{-# LANGUAGE DeriveDataTypeable #-} -- | -- Module : Statistics.Distribution.Beta -- Copyright : (c) 2010 Karamaan Group -- -- The beta distribution. module Statistics.Distribution.Beta ( BetaDistribution -- * Constructors , fromParams -- * Accessors , tridistA , tridistB , tridistC ) where import Control.Exception import Data.Generics import Foreign.C.Math.Double (gamma) import qualified Statistics.Distribution as D data BetaDistribution = BetaDist { alpha :: Double, beta :: Double } deriving (Eq, Read, Show, Typeable, Data) instance D.Distribution BetaDistribution where density (BetaDist a b) x = (gamma (a+b) / (gamma a * gamma b)) * (x**(a-1)) * ((1-x)**(b-1)) {-# INLINE density #-} cumulative (BetaDist a b) x = undefined {-# INLINE cumulative #-} quantile (BetaDist a b) p = undefined {-# INLINE quantile #-} instance D.Variance BetaDistribution where variance (BetaDist a b) = (a * b) / ((a+b)^2 * (a + b + 1)) {-# INLINE variance #-} instance D.Mean BetaDistribution where mean (BetaDist a b) = a / (a + b) {-# INLINE mean #-} fromParams :: Double -> Double -> BetaDistribution fromParams a b = assert (a > 0 && b > 0) (BetaDist a b) {-# INLINE fromParams #-}