{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
-- |
-- Module    : Statistics.Distribution.Poisson
-- Copyright : (c) 2009, 2011 Bryan O'Sullivan
-- License   : BSD3
--
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : portable
--
-- The Poisson distribution.  This is the discrete probability
-- distribution of a number of events occurring in a fixed interval if
-- these events occur with a known average rate, and occur
-- independently from each other within that interval.

module Statistics.Distribution.Poisson
    (
      PoissonDistribution
    -- * Constructors
    , poisson
    , poissonE
    -- * Accessors
    , poissonLambda
    -- * References
    -- $references
    ) where

import Control.Applicative
import Data.Aeson           (FromJSON(..), ToJSON, Value(..), (.:))
import Data.Binary          (Binary(..))
import Data.Data            (Data, Typeable)
import GHC.Generics         (Generic)
import Numeric.SpecFunctions (incompleteGamma,logFactorial)
import Numeric.MathFunctions.Constants (m_neg_inf)

import qualified Statistics.Distribution as D
import qualified Statistics.Distribution.Poisson.Internal as I
import Statistics.Internal



newtype PoissonDistribution = PD {
      PoissonDistribution -> Double
poissonLambda :: Double
    } deriving (PoissonDistribution -> PoissonDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoissonDistribution -> PoissonDistribution -> Bool
$c/= :: PoissonDistribution -> PoissonDistribution -> Bool
== :: PoissonDistribution -> PoissonDistribution -> Bool
$c== :: PoissonDistribution -> PoissonDistribution -> Bool
Eq, Typeable, Typeable PoissonDistribution
PoissonDistribution -> DataType
PoissonDistribution -> Constr
(forall b. Data b => b -> b)
-> PoissonDistribution -> PoissonDistribution
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) -> PoissonDistribution -> u
forall u.
(forall d. Data d => d -> u) -> PoissonDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PoissonDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PoissonDistribution
-> c PoissonDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PoissonDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PoissonDistribution)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PoissonDistribution -> m PoissonDistribution
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PoissonDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PoissonDistribution -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> PoissonDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> PoissonDistribution -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PoissonDistribution -> r
gmapT :: (forall b. Data b => b -> b)
-> PoissonDistribution -> PoissonDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> PoissonDistribution -> PoissonDistribution
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PoissonDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PoissonDistribution)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PoissonDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PoissonDistribution)
dataTypeOf :: PoissonDistribution -> DataType
$cdataTypeOf :: PoissonDistribution -> DataType
toConstr :: PoissonDistribution -> Constr
$ctoConstr :: PoissonDistribution -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PoissonDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PoissonDistribution
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PoissonDistribution
-> c PoissonDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PoissonDistribution
-> c PoissonDistribution
Data, forall x. Rep PoissonDistribution x -> PoissonDistribution
forall x. PoissonDistribution -> Rep PoissonDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoissonDistribution x -> PoissonDistribution
$cfrom :: forall x. PoissonDistribution -> Rep PoissonDistribution x
Generic)

instance Show PoissonDistribution where
  showsPrec :: Int -> PoissonDistribution -> ShowS
showsPrec Int
i (PD Double
l) = forall a. Show a => [Char] -> a -> Int -> ShowS
defaultShow1 [Char]
"poisson" Double
l Int
i
instance Read PoissonDistribution where
  readPrec :: ReadPrec PoissonDistribution
readPrec = forall a r. Read a => [Char] -> (a -> Maybe r) -> ReadPrec r
defaultReadPrecM1 [Char]
"poisson" Double -> Maybe PoissonDistribution
poissonE

instance ToJSON PoissonDistribution
instance FromJSON PoissonDistribution where
  parseJSON :: Value -> Parser PoissonDistribution
parseJSON (Object Object
v) = do
    Double
l <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"poissonLambda"
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Maybe PoissonDistribution
poissonE Double
l
  parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty

instance Binary PoissonDistribution where
  put :: PoissonDistribution -> Put
put = forall t. Binary t => t -> Put
put forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoissonDistribution -> Double
poissonLambda
  get :: Get PoissonDistribution
get = do
    Double
l <- forall t. Binary t => Get t
get
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Maybe PoissonDistribution
poissonE Double
l

instance D.Distribution PoissonDistribution where
    cumulative :: PoissonDistribution -> Double -> Double
cumulative (PD Double
lambda) Double
x
      | Double
x forall a. Ord a => a -> a -> Bool
< Double
0        = Double
0
      | forall a. RealFloat a => a -> Bool
isInfinite Double
x = Double
1
      | forall a. RealFloat a => a -> Bool
isNaN      Double
x = forall a. HasCallStack => [Char] -> a
error [Char]
"Statistics.Distribution.Poisson.cumulative: NaN input"
      | Bool
otherwise    = Double
1 forall a. Num a => a -> a -> a
- Double -> Double -> Double
incompleteGamma (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (RealFrac a, Integral b) => a -> b
floor Double
x forall a. Num a => a -> a -> a
+ Int
1 :: Int)) Double
lambda

instance D.DiscreteDistr PoissonDistribution where
    probability :: PoissonDistribution -> Int -> Double
probability (PD Double
lambda) Int
x = Double -> Double -> Double
I.probability Double
lambda (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x)
    logProbability :: PoissonDistribution -> Int -> Double
logProbability (PD Double
lambda) Int
i
      | Int
i forall a. Ord a => a -> a -> Bool
< Int
0     = Double
m_neg_inf
      | Bool
otherwise = forall a. Floating a => a -> a
log Double
lambda forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i forall a. Num a => a -> a -> a
- forall a. Integral a => a -> Double
logFactorial Int
i forall a. Num a => a -> a -> a
- Double
lambda

instance D.Variance PoissonDistribution where
    variance :: PoissonDistribution -> Double
variance = PoissonDistribution -> Double
poissonLambda

instance D.Mean PoissonDistribution where
    mean :: PoissonDistribution -> Double
mean = PoissonDistribution -> Double
poissonLambda

instance D.MaybeMean PoissonDistribution where
    maybeMean :: PoissonDistribution -> Maybe Double
maybeMean = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Mean d => d -> Double
D.mean

instance D.MaybeVariance PoissonDistribution where
    maybeStdDev :: PoissonDistribution -> Maybe Double
maybeStdDev   = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Variance d => d -> Double
D.stdDev

instance D.Entropy PoissonDistribution where
  entropy :: PoissonDistribution -> Double
entropy (PD Double
lambda) = Double -> Double
I.poissonEntropy Double
lambda

instance D.MaybeEntropy PoissonDistribution where
  maybeEntropy :: PoissonDistribution -> Maybe Double
maybeEntropy = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Entropy d => d -> Double
D.entropy

-- | Create Poisson distribution.
poisson :: Double -> PoissonDistribution
poisson :: Double -> PoissonDistribution
poisson Double
l = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ Double -> Maybe PoissonDistribution
poissonE Double
l

-- | Create Poisson distribution.
poissonE :: Double -> Maybe PoissonDistribution
poissonE :: Double -> Maybe PoissonDistribution
poissonE Double
l
  | Double
l forall a. Ord a => a -> a -> Bool
>=  Double
0   = forall a. a -> Maybe a
Just (Double -> PoissonDistribution
PD Double
l)
  | Bool
otherwise = forall a. Maybe a
Nothing

errMsg :: Double -> String
errMsg :: Double -> [Char]
errMsg Double
l = [Char]
"Statistics.Distribution.Poisson.poisson: lambda must be non-negative. Got "
        forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Double
l


-- $references
--
-- * Loader, C. (2000) Fast and Accurate Computation of Binomial
--   Probabilities. <http://projects.scipy.org/scipy/raw-attachment/ticket/620/loader2000Fast.pdf>
-- * Adell, J., Lekuona, A., and Yu, Y. (2010) Sharp Bounds on the
--   Entropy of the Poisson Law and Related Quantities
--   <http://arxiv.org/pdf/1001.2897.pdf>