mirror of
https://github.com/commercialhaskell/stackage.git
synced 2026-01-12 15:28:29 +01:00
Include bos/statistics#60 patch
This commit is contained in:
parent
048d21292a
commit
a9a59da45f
@ -320,9 +320,6 @@ defaultStablePackages ghcVer = unPackageMap $ execWriter $ do
|
||||
-- https://github.com/fpco/stackage/issues/72
|
||||
addRange "Michael Snoyman" "HaXml" "< 1.24"
|
||||
|
||||
-- Due to binary package dep
|
||||
addRange "Michael Snoyman" "statistics" "< 0.10.4"
|
||||
|
||||
-- Newest hxt requires network 2.4 or newest
|
||||
addRange "Michael Snoyman" "hxt" "< 9.3.1"
|
||||
addRange "Michael Snoyman" "network" "< 2.4"
|
||||
|
||||
707
patching/patches/statistics-0.10.5.2.patch
Normal file
707
patching/patches/statistics-0.10.5.2.patch
Normal file
@ -0,0 +1,707 @@
|
||||
diff -ru orig/Statistics/Distribution/Beta.hs new/Statistics/Distribution/Beta.hs
|
||||
--- orig/Statistics/Distribution/Beta.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Beta.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Beta
|
||||
@@ -27,6 +27,10 @@
|
||||
incompleteBeta, invIncompleteBeta, logBeta, digamma)
|
||||
import Numeric.MathFunctions.Constants (m_NaN)
|
||||
import qualified Statistics.Distribution as D
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
-- | The beta distribution
|
||||
data BetaDistribution = BD
|
||||
@@ -36,7 +40,11 @@
|
||||
-- ^ Beta shape parameter
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary BetaDistribution
|
||||
+instance Binary BetaDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (BD x y) = put x >> put y
|
||||
+ get = BD <$> get <*> get
|
||||
+#endif
|
||||
|
||||
-- | Create beta distribution. Both shape parameters must be positive.
|
||||
betaDistr :: Double -- ^ Shape parameter alpha
|
||||
diff -ru orig/Statistics/Distribution/Binomial.hs new/Statistics/Distribution/Binomial.hs
|
||||
--- orig/Statistics/Distribution/Binomial.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Binomial.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Binomial
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -30,6 +30,10 @@
|
||||
import qualified Statistics.Distribution.Poisson.Internal as I
|
||||
import Numeric.SpecFunctions (choose,incompleteBeta)
|
||||
import Numeric.MathFunctions.Constants (m_epsilon)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
|
||||
-- | The binomial distribution.
|
||||
@@ -40,7 +44,11 @@
|
||||
-- ^ Probability.
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary BinomialDistribution
|
||||
+instance Binary BinomialDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (BD x y) = put x >> put y
|
||||
+ get = BD <$> get <*> get
|
||||
+#endif
|
||||
|
||||
instance D.Distribution BinomialDistribution where
|
||||
cumulative = cumulative
|
||||
diff -ru orig/Statistics/Distribution/CauchyLorentz.hs new/Statistics/Distribution/CauchyLorentz.hs
|
||||
--- orig/Statistics/Distribution/CauchyLorentz.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/CauchyLorentz.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.CauchyLorentz
|
||||
-- Copyright : (c) 2011 Aleksey Khudyakov
|
||||
@@ -25,6 +25,10 @@
|
||||
import Data.Data (Data, Typeable)
|
||||
import GHC.Generics (Generic)
|
||||
import qualified Statistics.Distribution as D
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
-- | Cauchy-Lorentz distribution.
|
||||
data CauchyDistribution = CD {
|
||||
@@ -39,7 +43,11 @@
|
||||
}
|
||||
deriving (Eq, Show, Read, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary CauchyDistribution
|
||||
+instance Binary CauchyDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (CD x y) = put x >> put y
|
||||
+ get = CD <$> get <*> get
|
||||
+#endif
|
||||
|
||||
-- | Cauchy distribution
|
||||
cauchyDistribution :: Double -- ^ Central point
|
||||
diff -ru orig/Statistics/Distribution/ChiSquared.hs new/Statistics/Distribution/ChiSquared.hs
|
||||
--- orig/Statistics/Distribution/ChiSquared.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/ChiSquared.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.ChiSquared
|
||||
-- Copyright : (c) 2010 Alexey Khudyakov
|
||||
@@ -26,13 +26,20 @@
|
||||
|
||||
import qualified Statistics.Distribution as D
|
||||
import qualified System.Random.MWC.Distributions as MWC
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+#endif
|
||||
|
||||
|
||||
-- | Chi-squared distribution
|
||||
newtype ChiSquared = ChiSquared Int
|
||||
deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary ChiSquared
|
||||
+instance Binary ChiSquared where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = fmap ChiSquared get
|
||||
+ put (ChiSquared x) = put x
|
||||
+#endif
|
||||
|
||||
-- | Get number of degrees of freedom
|
||||
chiSquaredNDF :: ChiSquared -> Int
|
||||
diff -ru orig/Statistics/Distribution/Exponential.hs new/Statistics/Distribution/Exponential.hs
|
||||
--- orig/Statistics/Distribution/Exponential.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Exponential.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Exponential
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -31,13 +31,20 @@
|
||||
import qualified Statistics.Sample as S
|
||||
import qualified System.Random.MWC.Distributions as MWC
|
||||
import Statistics.Types (Sample)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+#endif
|
||||
|
||||
|
||||
newtype ExponentialDistribution = ED {
|
||||
edLambda :: Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary ExponentialDistribution
|
||||
+instance Binary ExponentialDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put = put . edLambda
|
||||
+ get = fmap ED get
|
||||
+#endif
|
||||
|
||||
instance D.Distribution ExponentialDistribution where
|
||||
cumulative = cumulative
|
||||
diff -ru orig/Statistics/Distribution/FDistribution.hs new/Statistics/Distribution/FDistribution.hs
|
||||
--- orig/Statistics/Distribution/FDistribution.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/FDistribution.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.FDistribution
|
||||
-- Copyright : (c) 2011 Aleksey Khudyakov
|
||||
@@ -23,6 +23,10 @@
|
||||
import qualified Statistics.Distribution as D
|
||||
import Numeric.SpecFunctions (
|
||||
logBeta, incompleteBeta, invIncompleteBeta, digamma)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
|
||||
|
||||
@@ -33,7 +37,11 @@
|
||||
}
|
||||
deriving (Eq, Show, Read, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary FDistribution
|
||||
+instance Binary FDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = F <$> get <*> get <*> get
|
||||
+ put (F x y z) = put x >> put y >> put z
|
||||
+#endif
|
||||
|
||||
fDistribution :: Int -> Int -> FDistribution
|
||||
fDistribution n m
|
||||
diff -ru orig/Statistics/Distribution/Gamma.hs new/Statistics/Distribution/Gamma.hs
|
||||
--- orig/Statistics/Distribution/Gamma.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Gamma.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Gamma
|
||||
-- Copyright : (c) 2009, 2011 Bryan O'Sullivan
|
||||
@@ -34,6 +34,10 @@
|
||||
import Statistics.Distribution.Poisson.Internal as Poisson
|
||||
import qualified Statistics.Distribution as D
|
||||
import qualified System.Random.MWC.Distributions as MWC
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
-- | The gamma distribution.
|
||||
data GammaDistribution = GD {
|
||||
@@ -41,7 +45,11 @@
|
||||
, gdScale :: {-# UNPACK #-} !Double -- ^ Scale parameter, ϑ.
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary GammaDistribution
|
||||
+instance Binary GammaDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (GD x y) = put x >> put y
|
||||
+ get = GD <$> get <*> get
|
||||
+#endif
|
||||
|
||||
-- | Create gamma distribution. Both shape and scale parameters must
|
||||
-- be positive.
|
||||
diff -ru orig/Statistics/Distribution/Geometric.hs new/Statistics/Distribution/Geometric.hs
|
||||
--- orig/Statistics/Distribution/Geometric.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Geometric.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Geometric
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -37,6 +37,10 @@
|
||||
import Numeric.MathFunctions.Constants(m_pos_inf,m_neg_inf)
|
||||
import qualified Statistics.Distribution as D
|
||||
import qualified System.Random.MWC.Distributions as MWC
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>))
|
||||
+#endif
|
||||
|
||||
----------------------------------------------------------------
|
||||
-- Distribution over [1..]
|
||||
@@ -45,7 +49,11 @@
|
||||
gdSuccess :: Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary GeometricDistribution
|
||||
+instance Binary GeometricDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = GD <$> get
|
||||
+ put (GD x) = put x
|
||||
+#endif
|
||||
|
||||
instance D.Distribution GeometricDistribution where
|
||||
cumulative = cumulative
|
||||
@@ -115,7 +123,11 @@
|
||||
gdSuccess0 :: Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary GeometricDistribution0
|
||||
+instance Binary GeometricDistribution0 where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = GD0 <$> get
|
||||
+ put (GD0 x) = put x
|
||||
+#endif
|
||||
|
||||
instance D.Distribution GeometricDistribution0 where
|
||||
cumulative (GD0 s) x = cumulative (GD s) (x + 1)
|
||||
diff -ru orig/Statistics/Distribution/Hypergeometric.hs new/Statistics/Distribution/Hypergeometric.hs
|
||||
--- orig/Statistics/Distribution/Hypergeometric.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Hypergeometric.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Hypergeometric
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -33,6 +33,10 @@
|
||||
import Numeric.MathFunctions.Constants (m_epsilon)
|
||||
import Numeric.SpecFunctions (choose)
|
||||
import qualified Statistics.Distribution as D
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
data HypergeometricDistribution = HD {
|
||||
hdM :: {-# UNPACK #-} !Int
|
||||
@@ -40,7 +44,11 @@
|
||||
, hdK :: {-# UNPACK #-} !Int
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary HypergeometricDistribution
|
||||
+instance Binary HypergeometricDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = HD <$> get <*> get <*> get
|
||||
+ put (HD x y z) = put x >> put y >> put z
|
||||
+#endif
|
||||
|
||||
instance D.Distribution HypergeometricDistribution where
|
||||
cumulative = cumulative
|
||||
diff -ru orig/Statistics/Distribution/Normal.hs new/Statistics/Distribution/Normal.hs
|
||||
--- orig/Statistics/Distribution/Normal.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Normal.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Normal
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -28,6 +28,10 @@
|
||||
import qualified Statistics.Distribution as D
|
||||
import qualified Statistics.Sample as S
|
||||
import qualified System.Random.MWC.Distributions as MWC
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
|
||||
|
||||
@@ -39,7 +43,9 @@
|
||||
, ndCdfDenom :: {-# UNPACK #-} !Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary NormalDistribution
|
||||
+instance Binary NormalDistribution where
|
||||
+ put (ND w x y z) = put w >> put x >> put y >> put z
|
||||
+ get = ND <$> get <*> get <*> get <*> get
|
||||
|
||||
instance D.Distribution NormalDistribution where
|
||||
cumulative = cumulative
|
||||
diff -ru orig/Statistics/Distribution/Poisson/Internal.hs new/Statistics/Distribution/Poisson/Internal.hs
|
||||
--- orig/Statistics/Distribution/Poisson/Internal.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Poisson/Internal.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -36,8 +36,8 @@
|
||||
-- | Compute entropy using Theorem 1 from "Sharp Bounds on the Entropy
|
||||
-- of the Poisson Law". This function is unused because 'directEntorpy'
|
||||
-- is just as accurate and is faster by about a factor of 4.
|
||||
-alyThm1 :: Double -> Double
|
||||
-alyThm1 lambda =
|
||||
+_alyThm1 :: Double -> Double
|
||||
+_alyThm1 lambda =
|
||||
sum (takeWhile (\x -> abs x >= m_epsilon * lll) alySeries) + lll
|
||||
where lll = lambda * (1 - log lambda)
|
||||
alySeries =
|
||||
@@ -175,4 +175,4 @@
|
||||
| lambda <= 18 = alyThm2 lambda upperCoefficients6 lowerCoefficients6
|
||||
| lambda <= 24 = alyThm2 lambda upperCoefficients8 lowerCoefficients8
|
||||
| lambda <= 30 = alyThm2 lambda upperCoefficients10 lowerCoefficients10
|
||||
- | otherwise = alyThm2 lambda upperCoefficients12 lowerCoefficients12
|
||||
\ No newline at end of file
|
||||
+ | otherwise = alyThm2 lambda upperCoefficients12 lowerCoefficients12
|
||||
diff -ru orig/Statistics/Distribution/Poisson.hs new/Statistics/Distribution/Poisson.hs
|
||||
--- orig/Statistics/Distribution/Poisson.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Poisson.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Poisson
|
||||
-- Copyright : (c) 2009, 2011 Bryan O'Sullivan
|
||||
@@ -31,13 +31,20 @@
|
||||
import qualified Statistics.Distribution.Poisson.Internal as I
|
||||
import Numeric.SpecFunctions (incompleteGamma,logFactorial)
|
||||
import Numeric.MathFunctions.Constants (m_neg_inf)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+#endif
|
||||
|
||||
|
||||
newtype PoissonDistribution = PD {
|
||||
poissonLambda :: Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary PoissonDistribution
|
||||
+instance Binary PoissonDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = fmap PD get
|
||||
+ put = put . poissonLambda
|
||||
+#endif
|
||||
|
||||
instance D.Distribution PoissonDistribution where
|
||||
cumulative (PD lambda) x
|
||||
@@ -78,8 +85,9 @@
|
||||
poisson :: Double -> PoissonDistribution
|
||||
poisson l
|
||||
| l >= 0 = PD l
|
||||
- | otherwise = error $ "Statistics.Distribution.Poisson.poisson:\
|
||||
- \ lambda must be non-negative. Got " ++ show l
|
||||
+ | otherwise = error $
|
||||
+ "Statistics.Distribution.Poisson.poisson: lambda must be non-negative. Got "
|
||||
+ ++ show l
|
||||
{-# INLINE poisson #-}
|
||||
|
||||
-- $references
|
||||
diff -ru orig/Statistics/Distribution/StudentT.hs new/Statistics/Distribution/StudentT.hs
|
||||
--- orig/Statistics/Distribution/StudentT.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/StudentT.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.StudentT
|
||||
-- Copyright : (c) 2011 Aleksey Khudyakov
|
||||
@@ -23,12 +23,19 @@
|
||||
import Statistics.Distribution.Transform (LinearTransform (..))
|
||||
import Numeric.SpecFunctions (
|
||||
logBeta, incompleteBeta, invIncompleteBeta, digamma)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+#endif
|
||||
|
||||
-- | Student-T distribution
|
||||
newtype StudentT = StudentT { studentTndf :: Double }
|
||||
deriving (Eq, Show, Read, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary StudentT
|
||||
+instance Binary StudentT where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put = put . studentTndf
|
||||
+ get = fmap StudentT get
|
||||
+#endif
|
||||
|
||||
-- | Create Student-T distribution. Number of parameters must be positive.
|
||||
studentT :: Double -> StudentT
|
||||
diff -ru orig/Statistics/Distribution/Transform.hs new/Statistics/Distribution/Transform.hs
|
||||
--- orig/Statistics/Distribution/Transform.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Transform.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts,
|
||||
- FlexibleInstances, UndecidableInstances #-}
|
||||
+ FlexibleInstances, UndecidableInstances, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Transform
|
||||
-- Copyright : (c) 2013 John McDonnell;
|
||||
@@ -21,6 +21,10 @@
|
||||
import GHC.Generics (Generic)
|
||||
import Data.Functor ((<$>))
|
||||
import qualified Statistics.Distribution as D
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<*>))
|
||||
+#endif
|
||||
|
||||
-- | Linear transformation applied to distribution.
|
||||
--
|
||||
@@ -35,7 +39,11 @@
|
||||
-- ^ Distribution being transformed.
|
||||
} deriving (Eq, Show, Read, Typeable, Data, Generic)
|
||||
|
||||
-instance (Binary d) => Binary (LinearTransform d)
|
||||
+instance (Binary d) => Binary (LinearTransform d) where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = LinearTransform <$> get <*> get <*> get
|
||||
+ put (LinearTransform x y z) = put x >> put y >> put z
|
||||
+#endif
|
||||
|
||||
-- | Apply linear transformation to distribution.
|
||||
scaleAround :: Double -- ^ Fixed point
|
||||
diff -ru orig/Statistics/Distribution/Uniform.hs new/Statistics/Distribution/Uniform.hs
|
||||
--- orig/Statistics/Distribution/Uniform.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Distribution/Uniform.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Distribution.Uniform
|
||||
-- Copyright : (c) 2011 Aleksey Khudyakov
|
||||
@@ -24,6 +24,10 @@
|
||||
import GHC.Generics (Generic)
|
||||
import qualified Statistics.Distribution as D
|
||||
import qualified System.Random.MWC as MWC
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
|
||||
-- | Uniform distribution from A to B
|
||||
@@ -32,7 +36,11 @@
|
||||
, uniformB :: {-# UNPACK #-} !Double -- ^ Upper boundary of distribution
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary UniformDistribution
|
||||
+instance Binary UniformDistribution where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (UniformDistribution x y) = put x >> put y
|
||||
+ get = UniformDistribution <$> get <*> get
|
||||
+#endif
|
||||
|
||||
-- | Create uniform distribution.
|
||||
uniformDistr :: Double -> Double -> UniformDistribution
|
||||
diff -ru orig/Statistics/Math/RootFinding.hs new/Statistics/Math/RootFinding.hs
|
||||
--- orig/Statistics/Math/RootFinding.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Math/RootFinding.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
|
||||
-- |
|
||||
-- Module : Statistics.Math.RootFinding
|
||||
@@ -27,6 +27,11 @@
|
||||
import Control.Monad (MonadPlus(..), ap)
|
||||
import Data.Data (Data, Typeable)
|
||||
import GHC.Generics (Generic)
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Data.Binary.Put (putWord8)
|
||||
+import Data.Binary.Get (getWord8)
|
||||
+#endif
|
||||
|
||||
|
||||
-- | The result of searching for a root of a mathematical function.
|
||||
@@ -40,7 +45,20 @@
|
||||
-- ^ A root was successfully found.
|
||||
deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance (Binary a) => Binary (Root a)
|
||||
+instance (Binary a) => Binary (Root a) where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put NotBracketed = putWord8 0
|
||||
+ put SearchFailed = putWord8 1
|
||||
+ put (Root a) = putWord8 2 >> put a
|
||||
+
|
||||
+ get = do
|
||||
+ i <- getWord8
|
||||
+ case i of
|
||||
+ 0 -> return NotBracketed
|
||||
+ 1 -> return SearchFailed
|
||||
+ 2 -> fmap Root get
|
||||
+ _ -> fail $ "Root.get: Invalid value: " ++ show i
|
||||
+#endif
|
||||
|
||||
instance Functor Root where
|
||||
fmap _ NotBracketed = NotBracketed
|
||||
diff -ru orig/Statistics/Resampling/Bootstrap.hs new/Statistics/Resampling/Bootstrap.hs
|
||||
--- orig/Statistics/Resampling/Bootstrap.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Resampling/Bootstrap.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, OverloadedStrings,
|
||||
- RecordWildCards #-}
|
||||
+ RecordWildCards, CPP #-}
|
||||
|
||||
-- |
|
||||
-- Module : Statistics.Resampling.Bootstrap
|
||||
@@ -35,6 +35,10 @@
|
||||
import Statistics.Sample (mean)
|
||||
import Statistics.Types (Estimator, Sample)
|
||||
import qualified Data.Vector.Unboxed as U
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+import Data.Binary (put, get)
|
||||
+import Control.Applicative ((<$>), (<*>))
|
||||
+#endif
|
||||
|
||||
-- | A point and interval estimate computed via an 'Estimator'.
|
||||
data Estimate = Estimate {
|
||||
@@ -50,7 +54,11 @@
|
||||
-- ^ Confidence level of the confidence intervals.
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary Estimate
|
||||
+instance Binary Estimate where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (Estimate w x y z) = put w >> put x >> put y >> put z
|
||||
+ get = Estimate <$> get <*> get <*> get <*> get
|
||||
+#endif
|
||||
instance NFData Estimate
|
||||
|
||||
-- | Multiply the point, lower bound, and upper bound in an 'Estimate'
|
||||
diff -ru orig/Statistics/Resampling.hs new/Statistics/Resampling.hs
|
||||
--- orig/Statistics/Resampling.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Resampling.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
|
||||
-- |
|
||||
-- Module : Statistics.Resampling
|
||||
@@ -42,7 +42,11 @@
|
||||
fromResample :: U.Vector Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary Resample
|
||||
+instance Binary Resample where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put = put . fromResample
|
||||
+ get = fmap Resample get
|
||||
+#endif
|
||||
|
||||
-- | /O(e*r*s)/ Resample a data set repeatedly, with replacement,
|
||||
-- computing each estimate over the resampled data.
|
||||
diff -ru orig/Statistics/Sample/KernelDensity/Simple.hs new/Statistics/Sample/KernelDensity/Simple.hs
|
||||
--- orig/Statistics/Sample/KernelDensity/Simple.hs 2014-02-19 18:51:48.640768606 +0200
|
||||
+++ new/Statistics/Sample/KernelDensity/Simple.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Sample.KernelDensity.Simple
|
||||
-- Copyright : (c) 2009 Bryan O'Sullivan
|
||||
@@ -61,7 +61,11 @@
|
||||
fromPoints :: U.Vector Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary Points
|
||||
+instance Binary Points where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ get = fmap Points get
|
||||
+ put = put . fromPoints
|
||||
+#endif
|
||||
|
||||
-- | Bandwidth estimator for an Epanechnikov kernel.
|
||||
epanechnikovBW :: Double -> Bandwidth
|
||||
diff -ru orig/Statistics/Sample/Powers.hs new/Statistics/Sample/Powers.hs
|
||||
--- orig/Statistics/Sample/Powers.hs 2014-02-19 18:51:48.636768606 +0200
|
||||
+++ new/Statistics/Sample/Powers.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric,
|
||||
- FlexibleContexts #-}
|
||||
+ FlexibleContexts, CPP #-}
|
||||
-- |
|
||||
-- Module : Statistics.Sample.Powers
|
||||
-- Copyright : (c) 2009, 2010 Bryan O'Sullivan
|
||||
@@ -65,7 +65,11 @@
|
||||
newtype Powers = Powers (U.Vector Double)
|
||||
deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
-instance Binary Powers
|
||||
+instance Binary Powers where
|
||||
+#if !MIN_VERSION_binary(0, 6, 0)
|
||||
+ put (Powers v) = put v
|
||||
+ get = fmap Powers get
|
||||
+#endif
|
||||
|
||||
-- | O(/n/) Collect the /n/ simple powers of a sample.
|
||||
--
|
||||
diff -ru orig/statistics.cabal new/statistics.cabal
|
||||
--- orig/statistics.cabal 2014-02-19 18:51:48.676768606 +0200
|
||||
+++ new/statistics.cabal 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -90,7 +90,7 @@
|
||||
Statistics.Test.Internal
|
||||
build-depends:
|
||||
base < 5,
|
||||
- binary >= 0.6.3.0,
|
||||
+ binary >= 0.5.1.0,
|
||||
deepseq >= 1.1.0.2,
|
||||
erf,
|
||||
monad-par >= 0.3.4,
|
||||
diff -ru orig/tests/Tests/Distribution.hs new/tests/Tests/Distribution.hs
|
||||
--- orig/tests/Tests/Distribution.hs 2014-02-19 18:51:48.676768606 +0200
|
||||
+++ new/tests/Tests/Distribution.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -188,7 +188,7 @@
|
||||
|
||||
-- Quantile is inverse of CDF
|
||||
quantileIsInvCDF :: (Param d, ContDistr d) => T d -> d -> Double -> Property
|
||||
-quantileIsInvCDF _ d (snd . properFraction -> p) =
|
||||
+quantileIsInvCDF _ d ((snd :: (Int, y) -> y) . properFraction -> p) =
|
||||
p > 0 && p < 1 ==> ( printTestCase (printf "Quantile = %g" q )
|
||||
$ printTestCase (printf "Probability = %g" p )
|
||||
$ printTestCase (printf "Probability' = %g" p')
|
||||
@@ -203,8 +203,8 @@
|
||||
quantileShouldFail :: (ContDistr d) => T d -> d -> Double -> Property
|
||||
quantileShouldFail _ d p =
|
||||
p < 0 || p > 1 ==> QC.monadicIO $ do r <- QC.run $ catch
|
||||
- (do { return $! quantile d p; return False })
|
||||
- (\(e :: SomeException) -> return True)
|
||||
+ (do { _ <- return $! quantile d p; return False })
|
||||
+ (\(_e :: SomeException) -> return True)
|
||||
QC.assert r
|
||||
|
||||
|
||||
diff -ru orig/tests/Tests/Function.hs new/tests/Tests/Function.hs
|
||||
--- orig/tests/Tests/Function.hs 2014-02-19 18:51:48.676768606 +0200
|
||||
+++ new/tests/Tests/Function.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -1,7 +1,6 @@
|
||||
module Tests.Function ( tests ) where
|
||||
|
||||
import qualified Data.Vector.Unboxed as U
|
||||
-import Data.Vector.Unboxed ((!))
|
||||
|
||||
import Test.QuickCheck
|
||||
import Test.Framework
|
||||
@@ -29,5 +28,5 @@
|
||||
p_nextHighestPowerOfTwo
|
||||
= all (\(good, is) -> all ((==good) . nextHighestPowerOfTwo) is) lists
|
||||
where
|
||||
- pows = [1 .. 17]
|
||||
+ pows = [1 .. 17 :: Int]
|
||||
lists = [ (2^m, [2^n+1 .. 2^m]) | (n,m) <- pows `zip` tail pows ]
|
||||
diff -ru orig/tests/Tests/Transform.hs new/tests/Tests/Transform.hs
|
||||
--- orig/tests/Tests/Transform.hs 2014-02-19 18:51:48.672768606 +0200
|
||||
+++ new/tests/Tests/Transform.hs 2014-02-19 18:51:48.000000000 +0200
|
||||
@@ -15,7 +15,7 @@
|
||||
import Test.Framework (Test, testGroup)
|
||||
import Test.Framework.Providers.QuickCheck2 (testProperty)
|
||||
import Test.QuickCheck (Positive(..),Property,Arbitrary(..),Gen,choose,vectorOf,
|
||||
- printTestCase, quickCheck)
|
||||
+ printTestCase)
|
||||
|
||||
import Text.Printf
|
||||
|
||||
Loading…
Reference in New Issue
Block a user