On Wed, 26 Sep 2007, ChrisK wrote:
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:
If it's only about polymorphic list types, a type class for general list
types may be enough. This works without multi-parameter type class.
http://software.complete.org/listlike/
Maybe it can be generalized to Foldable.
http://www.haskell.org/haskellwiki/Use_of_language_extensions
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe