{-# LANGUAGE OverloadedStrings #-}{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}-- |-- Module : Statistics.Distribution.Geometric-- Copyright : (c) 2009 Bryan O'Sullivan-- License : BSD3---- Maintainer : bos@serpentine.com-- Stability : experimental-- Portability : portable---- The Geometric distribution. There are two variants of-- distribution. First is the probability distribution of the number-- of Bernoulli trials needed to get one success, supported on the set-- [1,2..] ('GeometricDistribution'). Sometimes it's referred to as-- the /shifted/ geometric distribution to distinguish from another-- one.---- Second variant is probability distribution of the number of-- failures before first success, defined over the set [0,1..]-- ('GeometricDistribution0').moduleStatistics.Distribution.Geometric(GeometricDistribution ,GeometricDistribution0 -- * Constructors,geometric ,geometricE ,geometric0 ,geometric0E -- ** Accessors,gdSuccess ,gdSuccess0 )whereimportControl.ApplicativeimportControl.Monad(liftM)importData.Aeson(FromJSON(..),ToJSON,Value(..),(.:))importData.Binary(Binary(..))importData.Data(Data,Typeable)importGHC.Generics(Generic)importNumeric.MathFunctions.Constants(m_neg_inf)importNumeric.SpecFunctions(log1p,expm1)importqualifiedSystem.Random.MWC.DistributionsasMWCimportqualifiedStatistics.Distribution asDimportStatistics.Internal ------------------------------------------------------------------ | Distribution over [1..]newtypeGeometricDistribution =GD {GeometricDistribution -> Double gdSuccess ::Double}deriving(GeometricDistribution -> GeometricDistribution -> Bool (GeometricDistribution -> GeometricDistribution -> Bool) -> (GeometricDistribution -> GeometricDistribution -> Bool) -> Eq GeometricDistribution forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: GeometricDistribution -> GeometricDistribution -> Bool == :: GeometricDistribution -> GeometricDistribution -> Bool $c/= :: GeometricDistribution -> GeometricDistribution -> Bool /= :: GeometricDistribution -> GeometricDistribution -> Bool Eq,Typeable,Typeable GeometricDistribution Typeable GeometricDistribution => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution -> c GeometricDistribution) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution) -> (GeometricDistribution -> Constr) -> (GeometricDistribution -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution)) -> ((forall b. Data b => b -> b) -> GeometricDistribution -> GeometricDistribution) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r) -> (forall u. (forall d. Data d => d -> u) -> GeometricDistribution -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution) -> Data GeometricDistribution GeometricDistribution -> Constr GeometricDistribution -> DataType (forall b. Data b => b -> b) -> GeometricDistribution -> GeometricDistribution forall a. Typeable a => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution -> u forall u. (forall d. Data d => d -> u) -> GeometricDistribution -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution -> c GeometricDistribution forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution -> c GeometricDistribution gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution -> c GeometricDistribution $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution $ctoConstr :: GeometricDistribution -> Constr toConstr :: GeometricDistribution -> Constr $cdataTypeOf :: GeometricDistribution -> DataType dataTypeOf :: GeometricDistribution -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution) $cgmapT :: (forall b. Data b => b -> b) -> GeometricDistribution -> GeometricDistribution gmapT :: (forall b. Data b => b -> b) -> GeometricDistribution -> GeometricDistribution $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> GeometricDistribution -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> GeometricDistribution -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution -> m GeometricDistribution Data,(forall x. GeometricDistribution -> Rep GeometricDistribution x) -> (forall x. Rep GeometricDistribution x -> GeometricDistribution) -> Generic GeometricDistribution forall x. Rep GeometricDistribution x -> GeometricDistribution forall x. GeometricDistribution -> Rep GeometricDistribution x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. GeometricDistribution -> Rep GeometricDistribution x from :: forall x. GeometricDistribution -> Rep GeometricDistribution x $cto :: forall x. Rep GeometricDistribution x -> GeometricDistribution to :: forall x. Rep GeometricDistribution x -> GeometricDistribution Generic)instanceShowGeometricDistribution whereshowsPrec :: Int -> GeometricDistribution -> ShowS showsPrec Int i (GD Double x )=[Char] -> Double -> Int -> ShowS forall a. Show a => [Char] -> a -> Int -> ShowS defaultShow1 [Char] "geometric"Double x Int i instanceReadGeometricDistribution wherereadPrec :: ReadPrec GeometricDistribution readPrec =[Char] -> (Double -> Maybe GeometricDistribution) -> ReadPrec GeometricDistribution forall a r. Read a => [Char] -> (a -> Maybe r) -> ReadPrec r defaultReadPrecM1 [Char] "geometric"Double -> Maybe GeometricDistribution geometricE instanceToJSONGeometricDistribution instanceFromJSONGeometricDistribution whereparseJSON :: Value -> Parser GeometricDistribution parseJSON (ObjectObject v )=doDouble x <-Object v Object -> Key -> Parser Double forall a. FromJSON a => Object -> Key -> Parser a .:Key "gdSuccess"Parser GeometricDistribution -> (GeometricDistribution -> Parser GeometricDistribution) -> Maybe GeometricDistribution -> Parser GeometricDistribution forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> Parser GeometricDistribution forall a. [Char] -> Parser a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Parser GeometricDistribution) -> [Char] -> Parser GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg Double x )GeometricDistribution -> Parser GeometricDistribution forall a. a -> Parser a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe GeometricDistribution -> Parser GeometricDistribution) -> Maybe GeometricDistribution -> Parser GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution geometricE Double x parseJSONValue _=Parser GeometricDistribution forall a. Parser a forall (f :: * -> *) a. Alternative f => f a emptyinstanceBinaryGeometricDistribution whereput :: GeometricDistribution -> Put put (GD Double x )=Double -> Put forall t. Binary t => t -> Put putDouble x get :: Get GeometricDistribution get =doDouble x <-Get Double forall t. Binary t => Get t getGet GeometricDistribution -> (GeometricDistribution -> Get GeometricDistribution) -> Maybe GeometricDistribution -> Get GeometricDistribution forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> Get GeometricDistribution forall a. [Char] -> Get a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Get GeometricDistribution) -> [Char] -> Get GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg Double x )GeometricDistribution -> Get GeometricDistribution forall a. a -> Get a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe GeometricDistribution -> Get GeometricDistribution) -> Maybe GeometricDistribution -> Get GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution geometricE Double x instanceD.Distribution GeometricDistribution wherecumulative :: GeometricDistribution -> Double -> Double cumulative =GeometricDistribution -> Double -> Double cumulative complCumulative :: GeometricDistribution -> Double -> Double complCumulative =GeometricDistribution -> Double -> Double complCumulative instanceD.DiscreteDistr GeometricDistribution whereprobability :: GeometricDistribution -> Int -> Double probability (GD Double s )Int n |Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 1=Double 0|Double s Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >=Double 0.5=Double s Double -> Double -> Double forall a. Num a => a -> a -> a *(Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -Double s )Double -> Int -> Double forall a b. (Num a, Integral b) => a -> b -> a ^(Int n Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)|Bool otherwise=Double s Double -> Double -> Double forall a. Num a => a -> a -> a *(Double -> Double forall a. Floating a => a -> a exp(Double -> Double) -> Double -> Double forall a b. (a -> b) -> a -> b $Double -> Double forall a. Floating a => a -> a log1p(-Double s )Double -> Double -> Double forall a. Num a => a -> a -> a *(Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt n Double -> Double -> Double forall a. Num a => a -> a -> a -Double 1))logProbability :: GeometricDistribution -> Int -> Double logProbability (GD Double s )Int n |Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 1=Double m_neg_inf|Bool otherwise=Double -> Double forall a. Floating a => a -> a logDouble s Double -> Double -> Double forall a. Num a => a -> a -> a +Double -> Double forall a. Floating a => a -> a log1p(-Double s )Double -> Double -> Double forall a. Num a => a -> a -> a *(Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt n Double -> Double -> Double forall a. Num a => a -> a -> a -Double 1)instanceD.Mean GeometricDistribution wheremean :: GeometricDistribution -> Double mean (GD Double s )=Double 1Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double s instanceD.Variance GeometricDistribution wherevariance :: GeometricDistribution -> Double variance (GD Double s )=(Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -Double s )Double -> Double -> Double forall a. Fractional a => a -> a -> a /(Double s Double -> Double -> Double forall a. Num a => a -> a -> a *Double s )instanceD.MaybeMean GeometricDistribution wheremaybeMean :: GeometricDistribution -> Maybe Double maybeMean =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution -> Double) -> GeometricDistribution -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution -> Double forall d. Mean d => d -> Double D.mean instanceD.MaybeVariance GeometricDistribution wheremaybeStdDev :: GeometricDistribution -> Maybe Double maybeStdDev =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution -> Double) -> GeometricDistribution -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution -> Double forall d. Variance d => d -> Double D.stdDev maybeVariance :: GeometricDistribution -> Maybe Double maybeVariance =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution -> Double) -> GeometricDistribution -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution -> Double forall d. Variance d => d -> Double D.variance instanceD.Entropy GeometricDistribution whereentropy :: GeometricDistribution -> Double entropy (GD Double s )|Double s Double -> Double -> Bool forall a. Eq a => a -> a -> Bool ==Double 1=Double 0|Bool otherwise=-(Double s Double -> Double -> Double forall a. Num a => a -> a -> a *Double -> Double forall a. Floating a => a -> a logDouble s Double -> Double -> Double forall a. Num a => a -> a -> a +(Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -Double s )Double -> Double -> Double forall a. Num a => a -> a -> a *Double -> Double forall a. Floating a => a -> a log1p(-Double s ))Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double s instanceD.MaybeEntropy GeometricDistribution wheremaybeEntropy :: GeometricDistribution -> Maybe Double maybeEntropy =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution -> Double) -> GeometricDistribution -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution -> Double forall d. Entropy d => d -> Double D.entropy instanceD.DiscreteGen GeometricDistribution wheregenDiscreteVar :: forall g (m :: * -> *). StatefulGen g m => GeometricDistribution -> g -> m Int genDiscreteVar (GD Double s )g g =Double -> g -> m Int forall g (m :: * -> *). StatefulGen g m => Double -> g -> m Int MWC.geometric1Double s g g instanceD.ContGen GeometricDistribution wheregenContVar :: forall g (m :: * -> *). StatefulGen g m => GeometricDistribution -> g -> m Double genContVar GeometricDistribution d g g =Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Double) -> m Int -> m Double forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r `liftM`GeometricDistribution -> g -> m Int forall d g (m :: * -> *). (DiscreteGen d, StatefulGen g m) => d -> g -> m Int forall g (m :: * -> *). StatefulGen g m => GeometricDistribution -> g -> m Int D.genDiscreteVar GeometricDistribution d g g cumulative ::GeometricDistribution ->Double->Doublecumulative :: GeometricDistribution -> Double -> Double cumulative (GD Double s )Double x |Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <Double 1=Double 0|Double -> Bool forall a. RealFloat a => a -> Bool isInfiniteDouble x =Double 1|Double -> Bool forall a. RealFloat a => a -> Bool isNaNDouble x =[Char] -> Double forall a. HasCallStack => [Char] -> a error[Char] "Statistics.Distribution.Geometric.cumulative: NaN input"|Double s Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >=Double 0.5=Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -(Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -Double s )Double -> Int -> Double forall a b. (Num a, Integral b) => a -> b -> a ^Int k |Bool otherwise=Double -> Double forall a. Num a => a -> a negate(Double -> Double) -> Double -> Double forall a b. (a -> b) -> a -> b $Double -> Double forall a. Floating a => a -> a expm1(Double -> Double) -> Double -> Double forall a b. (a -> b) -> a -> b $Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt k Double -> Double -> Double forall a. Num a => a -> a -> a *Double -> Double forall a. Floating a => a -> a log1p(-Double s )wherek :: Int k =Double -> Int forall b. Integral b => Double -> b forall a b. (RealFrac a, Integral b) => a -> b floorDouble x ::IntcomplCumulative ::GeometricDistribution ->Double->DoublecomplCumulative :: GeometricDistribution -> Double -> Double complCumulative (GD Double s )Double x |Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <Double 1=Double 1|Double -> Bool forall a. RealFloat a => a -> Bool isInfiniteDouble x =Double 0|Double -> Bool forall a. RealFloat a => a -> Bool isNaNDouble x =[Char] -> Double forall a. HasCallStack => [Char] -> a error[Char] "Statistics.Distribution.Geometric.complCumulative: NaN input"|Double s Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >=Double 0.5=(Double 1Double -> Double -> Double forall a. Num a => a -> a -> a -Double s )Double -> Int -> Double forall a b. (Num a, Integral b) => a -> b -> a ^Int k |Bool otherwise=Double -> Double forall a. Floating a => a -> a exp(Double -> Double) -> Double -> Double forall a b. (a -> b) -> a -> b $Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt k Double -> Double -> Double forall a. Num a => a -> a -> a *Double -> Double forall a. Floating a => a -> a log1p(-Double s )wherek :: Int k =Double -> Int forall b. Integral b => Double -> b forall a b. (RealFrac a, Integral b) => a -> b floorDouble x ::Int-- | Create geometric distribution.geometric ::Double-- ^ Success rate->GeometricDistribution geometric :: Double -> GeometricDistribution geometric Double x =GeometricDistribution -> (GeometricDistribution -> GeometricDistribution) -> Maybe GeometricDistribution -> GeometricDistribution forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> GeometricDistribution forall a. HasCallStack => [Char] -> a error([Char] -> GeometricDistribution) -> [Char] -> GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg Double x )GeometricDistribution -> GeometricDistribution forall a. a -> a id(Maybe GeometricDistribution -> GeometricDistribution) -> Maybe GeometricDistribution -> GeometricDistribution forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution geometricE Double x -- | Create geometric distribution.geometricE ::Double-- ^ Success rate->MaybeGeometricDistribution geometricE :: Double -> Maybe GeometricDistribution geometricE Double x |Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >Double 0Bool -> Bool -> Bool &&Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <=Double 1=GeometricDistribution -> Maybe GeometricDistribution forall a. a -> Maybe a Just(Double -> GeometricDistribution GD Double x )|Bool otherwise=Maybe GeometricDistribution forall a. Maybe a NothingerrMsg ::Double->StringerrMsg :: Double -> [Char] errMsg Double x =[Char] "Statistics.Distribution.Geometric.geometric: probability must be in (0,1] range. Got "[Char] -> ShowS forall a. [a] -> [a] -> [a] ++Double -> [Char] forall a. Show a => a -> [Char] showDouble x ------------------------------------------------------------------ | Distribution over [0..]newtypeGeometricDistribution0 =GD0 {GeometricDistribution0 -> Double gdSuccess0 ::Double}deriving(GeometricDistribution0 -> GeometricDistribution0 -> Bool (GeometricDistribution0 -> GeometricDistribution0 -> Bool) -> (GeometricDistribution0 -> GeometricDistribution0 -> Bool) -> Eq GeometricDistribution0 forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: GeometricDistribution0 -> GeometricDistribution0 -> Bool == :: GeometricDistribution0 -> GeometricDistribution0 -> Bool $c/= :: GeometricDistribution0 -> GeometricDistribution0 -> Bool /= :: GeometricDistribution0 -> GeometricDistribution0 -> Bool Eq,Typeable,Typeable GeometricDistribution0 Typeable GeometricDistribution0 => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution0 -> c GeometricDistribution0) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution0) -> (GeometricDistribution0 -> Constr) -> (GeometricDistribution0 -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution0)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution0)) -> ((forall b. Data b => b -> b) -> GeometricDistribution0 -> GeometricDistribution0) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r) -> (forall u. (forall d. Data d => d -> u) -> GeometricDistribution0 -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution0 -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0) -> Data GeometricDistribution0 GeometricDistribution0 -> Constr GeometricDistribution0 -> DataType (forall b. Data b => b -> b) -> GeometricDistribution0 -> GeometricDistribution0 forall a. Typeable a => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution0 -> u forall u. (forall d. Data d => d -> u) -> GeometricDistribution0 -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution0 forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution0 -> c GeometricDistribution0 forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution0) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution0) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution0 -> c GeometricDistribution0 gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeometricDistribution0 -> c GeometricDistribution0 $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution0 gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeometricDistribution0 $ctoConstr :: GeometricDistribution0 -> Constr toConstr :: GeometricDistribution0 -> Constr $cdataTypeOf :: GeometricDistribution0 -> DataType dataTypeOf :: GeometricDistribution0 -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution0) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GeometricDistribution0) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution0) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeometricDistribution0) $cgmapT :: (forall b. Data b => b -> b) -> GeometricDistribution0 -> GeometricDistribution0 gmapT :: (forall b. Data b => b -> b) -> GeometricDistribution0 -> GeometricDistribution0 $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeometricDistribution0 -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> GeometricDistribution0 -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> GeometricDistribution0 -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution0 -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GeometricDistribution0 -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> GeometricDistribution0 -> m GeometricDistribution0 Data,(forall x. GeometricDistribution0 -> Rep GeometricDistribution0 x) -> (forall x. Rep GeometricDistribution0 x -> GeometricDistribution0) -> Generic GeometricDistribution0 forall x. Rep GeometricDistribution0 x -> GeometricDistribution0 forall x. GeometricDistribution0 -> Rep GeometricDistribution0 x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. GeometricDistribution0 -> Rep GeometricDistribution0 x from :: forall x. GeometricDistribution0 -> Rep GeometricDistribution0 x $cto :: forall x. Rep GeometricDistribution0 x -> GeometricDistribution0 to :: forall x. Rep GeometricDistribution0 x -> GeometricDistribution0 Generic)instanceShowGeometricDistribution0 whereshowsPrec :: Int -> GeometricDistribution0 -> ShowS showsPrecInt i (GD0 Double x )=[Char] -> Double -> Int -> ShowS forall a. Show a => [Char] -> a -> Int -> ShowS defaultShow1 [Char] "geometric0"Double x Int i instanceReadGeometricDistribution0 wherereadPrec :: ReadPrec GeometricDistribution0 readPrec=[Char] -> (Double -> Maybe GeometricDistribution0) -> ReadPrec GeometricDistribution0 forall a r. Read a => [Char] -> (a -> Maybe r) -> ReadPrec r defaultReadPrecM1 [Char] "geometric0"Double -> Maybe GeometricDistribution0 geometric0E instanceToJSONGeometricDistribution0 instanceFromJSONGeometricDistribution0 whereparseJSON :: Value -> Parser GeometricDistribution0 parseJSON(ObjectObject v )=doDouble x <-Object v Object -> Key -> Parser Double forall a. FromJSON a => Object -> Key -> Parser a .:Key "gdSuccess0"Parser GeometricDistribution0 -> (GeometricDistribution0 -> Parser GeometricDistribution0) -> Maybe GeometricDistribution0 -> Parser GeometricDistribution0 forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> Parser GeometricDistribution0 forall a. [Char] -> Parser a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Parser GeometricDistribution0) -> [Char] -> Parser GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg Double x )GeometricDistribution0 -> Parser GeometricDistribution0 forall a. a -> Parser a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe GeometricDistribution0 -> Parser GeometricDistribution0) -> Maybe GeometricDistribution0 -> Parser GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution0 geometric0E Double x parseJSONValue _=Parser GeometricDistribution0 forall a. Parser a forall (f :: * -> *) a. Alternative f => f a emptyinstanceBinaryGeometricDistribution0 whereput :: GeometricDistribution0 -> Put put(GD0 Double x )=Double -> Put forall t. Binary t => t -> Put putDouble x get :: Get GeometricDistribution0 get=doDouble x <-Get Double forall t. Binary t => Get t getGet GeometricDistribution0 -> (GeometricDistribution0 -> Get GeometricDistribution0) -> Maybe GeometricDistribution0 -> Get GeometricDistribution0 forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> Get GeometricDistribution0 forall a. [Char] -> Get a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Get GeometricDistribution0) -> [Char] -> Get GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg Double x )GeometricDistribution0 -> Get GeometricDistribution0 forall a. a -> Get a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe GeometricDistribution0 -> Get GeometricDistribution0) -> Maybe GeometricDistribution0 -> Get GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution0 geometric0E Double x instanceD.Distribution GeometricDistribution0 wherecumulative :: GeometricDistribution0 -> Double -> Double cumulative (GD0 Double s )Double x =GeometricDistribution -> Double -> Double cumulative (Double -> GeometricDistribution GD Double s )(Double x Double -> Double -> Double forall a. Num a => a -> a -> a +Double 1)complCumulative :: GeometricDistribution0 -> Double -> Double complCumulative (GD0 Double s )Double x =GeometricDistribution -> Double -> Double complCumulative (Double -> GeometricDistribution GD Double s )(Double x Double -> Double -> Double forall a. Num a => a -> a -> a +Double 1)instanceD.DiscreteDistr GeometricDistribution0 whereprobability :: GeometricDistribution0 -> Int -> Double probability (GD0 Double s )Int n =GeometricDistribution -> Int -> Double forall d. DiscreteDistr d => d -> Int -> Double D.probability (Double -> GeometricDistribution GD Double s )(Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1)logProbability :: GeometricDistribution0 -> Int -> Double logProbability (GD0 Double s )Int n =GeometricDistribution -> Int -> Double forall d. DiscreteDistr d => d -> Int -> Double D.logProbability (Double -> GeometricDistribution GD Double s )(Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1)instanceD.Mean GeometricDistribution0 wheremean :: GeometricDistribution0 -> Double mean (GD0 Double s )=Double 1Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double s Double -> Double -> Double forall a. Num a => a -> a -> a -Double 1instanceD.Variance GeometricDistribution0 wherevariance :: GeometricDistribution0 -> Double variance (GD0 Double s )=GeometricDistribution -> Double forall d. Variance d => d -> Double D.variance (Double -> GeometricDistribution GD Double s )instanceD.MaybeMean GeometricDistribution0 wheremaybeMean :: GeometricDistribution0 -> Maybe Double maybeMean =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution0 -> Double) -> GeometricDistribution0 -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution0 -> Double forall d. Mean d => d -> Double D.mean instanceD.MaybeVariance GeometricDistribution0 wheremaybeStdDev :: GeometricDistribution0 -> Maybe Double maybeStdDev =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution0 -> Double) -> GeometricDistribution0 -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution0 -> Double forall d. Variance d => d -> Double D.stdDev maybeVariance :: GeometricDistribution0 -> Maybe Double maybeVariance =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution0 -> Double) -> GeometricDistribution0 -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution0 -> Double forall d. Variance d => d -> Double D.variance instanceD.Entropy GeometricDistribution0 whereentropy :: GeometricDistribution0 -> Double entropy (GD0 Double s )=GeometricDistribution -> Double forall d. Entropy d => d -> Double D.entropy (Double -> GeometricDistribution GD Double s )instanceD.MaybeEntropy GeometricDistribution0 wheremaybeEntropy :: GeometricDistribution0 -> Maybe Double maybeEntropy =Double -> Maybe Double forall a. a -> Maybe a Just(Double -> Maybe Double) -> (GeometricDistribution0 -> Double) -> GeometricDistribution0 -> Maybe Double forall b c a. (b -> c) -> (a -> b) -> a -> c .GeometricDistribution0 -> Double forall d. Entropy d => d -> Double D.entropy instanceD.DiscreteGen GeometricDistribution0 wheregenDiscreteVar :: forall g (m :: * -> *). StatefulGen g m => GeometricDistribution0 -> g -> m Int genDiscreteVar (GD0 Double s )g g =Double -> g -> m Int forall g (m :: * -> *). StatefulGen g m => Double -> g -> m Int MWC.geometric0Double s g g instanceD.ContGen GeometricDistribution0 wheregenContVar :: forall g (m :: * -> *). StatefulGen g m => GeometricDistribution0 -> g -> m Double genContVar GeometricDistribution0 d g g =Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Double) -> m Int -> m Double forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r `liftM`GeometricDistribution0 -> g -> m Int forall d g (m :: * -> *). (DiscreteGen d, StatefulGen g m) => d -> g -> m Int forall g (m :: * -> *). StatefulGen g m => GeometricDistribution0 -> g -> m Int D.genDiscreteVar GeometricDistribution0 d g g -- | Create geometric distribution.geometric0 ::Double-- ^ Success rate->GeometricDistribution0 geometric0 :: Double -> GeometricDistribution0 geometric0 Double x =GeometricDistribution0 -> (GeometricDistribution0 -> GeometricDistribution0) -> Maybe GeometricDistribution0 -> GeometricDistribution0 forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> GeometricDistribution0 forall a. HasCallStack => [Char] -> a error([Char] -> GeometricDistribution0) -> [Char] -> GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> [Char] errMsg0 Double x )GeometricDistribution0 -> GeometricDistribution0 forall a. a -> a id(Maybe GeometricDistribution0 -> GeometricDistribution0) -> Maybe GeometricDistribution0 -> GeometricDistribution0 forall a b. (a -> b) -> a -> b $Double -> Maybe GeometricDistribution0 geometric0E Double x -- | Create geometric distribution.geometric0E ::Double-- ^ Success rate->MaybeGeometricDistribution0 geometric0E :: Double -> Maybe GeometricDistribution0 geometric0E Double x |Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >Double 0Bool -> Bool -> Bool &&Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <=Double 1=GeometricDistribution0 -> Maybe GeometricDistribution0 forall a. a -> Maybe a Just(Double -> GeometricDistribution0 GD0 Double x )|Bool otherwise=Maybe GeometricDistribution0 forall a. Maybe a NothingerrMsg0 ::Double->StringerrMsg0 :: Double -> [Char] errMsg0 Double x =[Char] "Statistics.Distribution.Geometric.geometric0: probability must be in (0,1] range. Got "[Char] -> ShowS forall a. [a] -> [a] -> [a] ++Double -> [Char] forall a. Show a => a -> [Char] showDouble x