[Haskell-cafe] Re: Math.Statistics
ChrisK
haskell at list.mightyreason.com
Wed Sep 26 01:31:13 EDT 2007
ok wrote:
> There are a number of interesting issues raised by mbeddoe's
> Math.Statistics.
>
> data (Floating a, Ord a)
> => Simple_Continuous_Variate a
> = SCV [a] Int a a (Array Int a)
>
> list_to_variate xs = SCV xs n m s o
> where n = length xs
> m = sum xs / fromIntegral n
> s = sum [(x - m)^2 | x <- xs] / fromIntegral (n - 1)
> o = listArray (1,n) (sort xs)
>
> vLength (SCV _ n _ _ _) = n
> vMean (SCV _ _ m _ _) = m
> vSd (SCV _ _ _ s _) = s
> vMin (SCV _ _ _ _ a) = a ! 1
> vMax (SCV _ n _ _ a) = a ! n
> vRange scv = vMax scv - vMin scv
> vMedian (SCV _ n _ _ a)
> | odd n = a ! ((n+1)`div`2)
> | even n = ((a ! l) + (a ! u))/2
> where l = n `div` 2
> u = n - l
> .....
Math.Statistics eats many good names. I would also suggest offering a type class
interface. Then you could operate on various containers besides a list:
-- A class for extracting a summary number from a type.
-- None of these make much sense without Ord.
-- I could imagine using (+) and `div` so why require (/)?
class (Ord b) => SingleStat a b | a -> b where
samples :: a -> Integer -- lump in with SingleStat
mean :: a -> b
var :: a -> b
stddev :: a -> b
moment :: Int -> a -> b
range :: a -> b
min :: a -> b
max :: a -> b
median :: a -> b
instance SingleStat [Integer] Integer where ...
instance SingleStat [Double] Double where ...
instance (Ix i) => SingleStat (Array i Double) Double where ...
instance SingleStat (Simple_Continuous_Variate a) where ...
-- And then I could make interesting things like Histogram,
-- where the data is Int's but the statistics are Doubles:
newtype Histogram = Histogram (Map Int Int)
instance SingleStat Histogram Double where ...
Cheers,
Chris
More information about the Haskell-Cafe
mailing list