{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
module Statistics.Distribution.Normal
(
NormalDistribution
, normalDistr
, normalDistrE
, normalDistrErr
, standard
) 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.MathFunctions.Constants (m_sqrt_2, m_sqrt_2_pi)
import Numeric.SpecFunctions (erfc, invErfc)
import qualified System.Random.MWC.Distributions as MWC
import qualified Data.Vector.Generic as G
import qualified Statistics.Distribution as D
import qualified Statistics.Sample as S
import Statistics.Internal
data NormalDistribution = ND {
NormalDistribution -> Double
mean :: {-# UNPACK #-} !Double
, NormalDistribution -> Double
stdDev :: {-# UNPACK #-} !Double
, NormalDistribution -> Double
ndPdfDenom :: {-# UNPACK #-} !Double
, NormalDistribution -> Double
ndCdfDenom :: {-# UNPACK #-} !Double
} deriving (NormalDistribution -> NormalDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalDistribution -> NormalDistribution -> Bool
$c/= :: NormalDistribution -> NormalDistribution -> Bool
== :: NormalDistribution -> NormalDistribution -> Bool
$c== :: NormalDistribution -> NormalDistribution -> Bool
Eq, Typeable, Typeable NormalDistribution
NormalDistribution -> DataType
NormalDistribution -> Constr
(forall b. Data b => b -> b)
-> NormalDistribution -> NormalDistribution
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) -> NormalDistribution -> u
forall u. (forall d. Data d => d -> u) -> NormalDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NormalDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NormalDistribution
-> c NormalDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NormalDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NormalDistribution)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NormalDistribution -> m NormalDistribution
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NormalDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NormalDistribution -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NormalDistribution -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NormalDistribution -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NormalDistribution -> r
gmapT :: (forall b. Data b => b -> b)
-> NormalDistribution -> NormalDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> NormalDistribution -> NormalDistribution
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NormalDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NormalDistribution)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NormalDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NormalDistribution)
dataTypeOf :: NormalDistribution -> DataType
$cdataTypeOf :: NormalDistribution -> DataType
toConstr :: NormalDistribution -> Constr
$ctoConstr :: NormalDistribution -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NormalDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NormalDistribution
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NormalDistribution
-> c NormalDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NormalDistribution
-> c NormalDistribution
Data, forall x. Rep NormalDistribution x -> NormalDistribution
forall x. NormalDistribution -> Rep NormalDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NormalDistribution x -> NormalDistribution
$cfrom :: forall x. NormalDistribution -> Rep NormalDistribution x
Generic)
instance Show NormalDistribution where
showsPrec :: Int -> NormalDistribution -> ShowS
showsPrec Int
i (ND Double
m Double
s Double
_ Double
_) = forall a b. (Show a, Show b) => [Char] -> a -> b -> Int -> ShowS
defaultShow2 [Char]
"normalDistr" Double
m Double
s Int
i
instance Read NormalDistribution where
readPrec :: ReadPrec NormalDistribution
readPrec = forall a b r.
(Read a, Read b) =>
[Char] -> (a -> b -> Maybe r) -> ReadPrec r
defaultReadPrecM2 [Char]
"normalDistr" Double -> Double -> Maybe NormalDistribution
normalDistrE
instance ToJSON NormalDistribution
instance FromJSON NormalDistribution where
parseJSON :: Value -> Parser NormalDistribution
parseJSON (Object Object
v) = do
Double
m <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mean"
Double
sd <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stdDev"
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Double -> Either [Char] NormalDistribution
normalDistrErr Double
m Double
sd
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
instance Binary NormalDistribution where
put :: NormalDistribution -> Put
put (ND Double
m Double
sd Double
_ Double
_) = forall t. Binary t => t -> Put
put Double
m forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Double
sd
get :: Get NormalDistribution
get = do
Double
m <- forall t. Binary t => Get t
get
Double
sd <- forall t. Binary t => Get t
get
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Double -> Either [Char] NormalDistribution
normalDistrErr Double
m Double
sd
instance D.Distribution NormalDistribution where
cumulative :: NormalDistribution -> Double -> Double
cumulative = NormalDistribution -> Double -> Double
cumulative
complCumulative :: NormalDistribution -> Double -> Double
complCumulative = NormalDistribution -> Double -> Double
complCumulative
instance D.ContDistr NormalDistribution where
logDensity :: NormalDistribution -> Double -> Double
logDensity = NormalDistribution -> Double -> Double
logDensity
quantile :: NormalDistribution -> Double -> Double
quantile = NormalDistribution -> Double -> Double
quantile
complQuantile :: NormalDistribution -> Double -> Double
complQuantile = NormalDistribution -> Double -> Double
complQuantile
instance D.MaybeMean NormalDistribution where
maybeMean :: NormalDistribution -> 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.Mean NormalDistribution where
mean :: NormalDistribution -> Double
mean = NormalDistribution -> Double
mean
instance D.MaybeVariance NormalDistribution where
maybeStdDev :: NormalDistribution -> 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
maybeVariance :: NormalDistribution -> Maybe Double
maybeVariance = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Variance d => d -> Double
D.variance
instance D.Variance NormalDistribution where
stdDev :: NormalDistribution -> Double
stdDev = NormalDistribution -> Double
stdDev
instance D.Entropy NormalDistribution where
entropy :: NormalDistribution -> Double
entropy NormalDistribution
d = Double
0.5 forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
log (Double
2 forall a. Num a => a -> a -> a
* forall a. Floating a => a
pi forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
exp Double
1 forall a. Num a => a -> a -> a
* forall d. Variance d => d -> Double
D.variance NormalDistribution
d)
instance D.MaybeEntropy NormalDistribution where
maybeEntropy :: NormalDistribution -> 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
instance D.ContGen NormalDistribution where
genContVar :: forall g (m :: * -> *).
StatefulGen g m =>
NormalDistribution -> g -> m Double
genContVar NormalDistribution
d = forall g (m :: * -> *).
StatefulGen g m =>
Double -> Double -> g -> m Double
MWC.normal (NormalDistribution -> Double
mean NormalDistribution
d) (NormalDistribution -> Double
stdDev NormalDistribution
d)
standard :: NormalDistribution
standard :: NormalDistribution
standard = ND { mean :: Double
mean = Double
0.0
, stdDev :: Double
stdDev = Double
1.0
, ndPdfDenom :: Double
ndPdfDenom = forall a. Floating a => a -> a
log Double
m_sqrt_2_pi
, ndCdfDenom :: Double
ndCdfDenom = Double
m_sqrt_2
}
normalDistr :: Double
-> Double
-> NormalDistribution
normalDistr :: Double -> Double -> NormalDistribution
normalDistr Double
m Double
sd = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. HasCallStack => [Char] -> a
error forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ Double -> Double -> Either [Char] NormalDistribution
normalDistrErr Double
m Double
sd
normalDistrE :: Double
-> Double
-> Maybe NormalDistribution
normalDistrE :: Double -> Double -> Maybe NormalDistribution
normalDistrE Double
m Double
sd = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Double -> Double -> Either [Char] NormalDistribution
normalDistrErr Double
m Double
sd
normalDistrErr :: Double
-> Double
-> Either String NormalDistribution
normalDistrErr :: Double -> Double -> Either [Char] NormalDistribution
normalDistrErr Double
m Double
sd
| Double
sd forall a. Ord a => a -> a -> Bool
> Double
0 = forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ ND { mean :: Double
mean = Double
m
, stdDev :: Double
stdDev = Double
sd
, ndPdfDenom :: Double
ndPdfDenom = forall a. Floating a => a -> a
log forall a b. (a -> b) -> a -> b
$ Double
m_sqrt_2_pi forall a. Num a => a -> a -> a
* Double
sd
, ndCdfDenom :: Double
ndCdfDenom = Double
m_sqrt_2 forall a. Num a => a -> a -> a
* Double
sd
}
| Bool
otherwise = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Double -> Double -> [Char]
errMsg Double
m Double
sd
errMsg :: Double -> Double -> String
errMsg :: Double -> Double -> [Char]
errMsg Double
_ Double
sd = [Char]
"Statistics.Distribution.Normal.normalDistr: standard deviation must be positive. Got " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Double
sd
instance D.FromSample NormalDistribution Double where
fromSample :: forall (v :: * -> *).
Vector v Double =>
v Double -> Maybe NormalDistribution
fromSample v Double
xs
| forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v Double
xs forall a. Ord a => a -> a -> Bool
<= Int
1 = forall a. Maybe a
Nothing
| Double
v forall a. Eq a => a -> a -> Bool
== Double
0 = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! Double -> Double -> NormalDistribution
normalDistr Double
m (forall a. Floating a => a -> a
sqrt Double
v)
where
(Double
m,Double
v) = forall (v :: * -> *).
Vector v Double =>
v Double -> (Double, Double)
S.meanVariance v Double
xs
logDensity :: NormalDistribution -> Double -> Double
logDensity :: NormalDistribution -> Double -> Double
logDensity NormalDistribution
d Double
x = (-Double
xm forall a. Num a => a -> a -> a
* Double
xm forall a. Fractional a => a -> a -> a
/ (Double
2 forall a. Num a => a -> a -> a
* Double
sd forall a. Num a => a -> a -> a
* Double
sd)) forall a. Num a => a -> a -> a
- NormalDistribution -> Double
ndPdfDenom NormalDistribution
d
where xm :: Double
xm = Double
x forall a. Num a => a -> a -> a
- NormalDistribution -> Double
mean NormalDistribution
d
sd :: Double
sd = NormalDistribution -> Double
stdDev NormalDistribution
d
cumulative :: NormalDistribution -> Double -> Double
cumulative :: NormalDistribution -> Double -> Double
cumulative NormalDistribution
d Double
x = Double -> Double
erfc ((NormalDistribution -> Double
mean NormalDistribution
d forall a. Num a => a -> a -> a
- Double
x) forall a. Fractional a => a -> a -> a
/ NormalDistribution -> Double
ndCdfDenom NormalDistribution
d) forall a. Fractional a => a -> a -> a
/ Double
2
complCumulative :: NormalDistribution -> Double -> Double
complCumulative :: NormalDistribution -> Double -> Double
complCumulative NormalDistribution
d Double
x = Double -> Double
erfc ((Double
x forall a. Num a => a -> a -> a
- NormalDistribution -> Double
mean NormalDistribution
d) forall a. Fractional a => a -> a -> a
/ NormalDistribution -> Double
ndCdfDenom NormalDistribution
d) forall a. Fractional a => a -> a -> a
/ Double
2
quantile :: NormalDistribution -> Double -> Double
quantile :: NormalDistribution -> Double -> Double
quantile NormalDistribution
d Double
p
| Double
p forall a. Eq a => a -> a -> Bool
== Double
0 = -Double
inf
| Double
p forall a. Eq a => a -> a -> Bool
== Double
1 = Double
inf
| Double
p forall a. Eq a => a -> a -> Bool
== Double
0.5 = NormalDistribution -> Double
mean NormalDistribution
d
| Double
p forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
p forall a. Ord a => a -> a -> Bool
< Double
1 = Double
x forall a. Num a => a -> a -> a
* NormalDistribution -> Double
ndCdfDenom NormalDistribution
d forall a. Num a => a -> a -> a
+ NormalDistribution -> Double
mean NormalDistribution
d
| Bool
otherwise =
forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Normal.quantile: p must be in [0,1] range. Got: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show Double
p
where x :: Double
x = - Double -> Double
invErfc (Double
2 forall a. Num a => a -> a -> a
* Double
p)
inf :: Double
inf = Double
1forall a. Fractional a => a -> a -> a
/Double
0
complQuantile :: NormalDistribution -> Double -> Double
complQuantile :: NormalDistribution -> Double -> Double
complQuantile NormalDistribution
d Double
p
| Double
p forall a. Eq a => a -> a -> Bool
== Double
0 = Double
inf
| Double
p forall a. Eq a => a -> a -> Bool
== Double
1 = -Double
inf
| Double
p forall a. Eq a => a -> a -> Bool
== Double
0.5 = NormalDistribution -> Double
mean NormalDistribution
d
| Double
p forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
p forall a. Ord a => a -> a -> Bool
< Double
1 = Double
x forall a. Num a => a -> a -> a
* NormalDistribution -> Double
ndCdfDenom NormalDistribution
d forall a. Num a => a -> a -> a
+ NormalDistribution -> Double
mean NormalDistribution
d
| Bool
otherwise =
forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Normal.complQuantile: p must be in [0,1] range. Got: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show Double
p
where x :: Double
x = Double -> Double
invErfc (Double
2 forall a. Num a => a -> a -> a
* Double
p)
inf :: Double
inf = Double
1forall a. Fractional a => a -> a -> a
/Double
0