mirror of
https://github.com/commercialhaskell/stackage.git
synced 2026-01-12 07:18:31 +01:00
Fixed a patch
This commit is contained in:
parent
8d967a65c6
commit
b1571f2c70
@ -1,6 +1,6 @@
|
||||
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
|
||||
--- orig/Statistics/Distribution/Beta.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Beta.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -32,8 +32,8 @@ diff -ru orig/Statistics/Distribution/Beta.hs new/Statistics/Distribution/Beta.h
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/Binomial.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Binomial.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -65,8 +65,8 @@ diff -ru orig/Statistics/Distribution/Binomial.hs new/Statistics/Distribution/Bi
|
||||
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
|
||||
--- orig/Statistics/Distribution/CauchyLorentz.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/CauchyLorentz.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -98,8 +98,8 @@ diff -ru orig/Statistics/Distribution/CauchyLorentz.hs new/Statistics/Distributi
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/ChiSquared.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/ChiSquared.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -129,8 +129,8 @@ diff -ru orig/Statistics/Distribution/ChiSquared.hs new/Statistics/Distribution/
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/Exponential.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Exponential.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -160,8 +160,8 @@ diff -ru orig/Statistics/Distribution/Exponential.hs new/Statistics/Distribution
|
||||
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
|
||||
--- orig/Statistics/Distribution/FDistribution.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/FDistribution.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -193,8 +193,8 @@ diff -ru orig/Statistics/Distribution/FDistribution.hs new/Statistics/Distributi
|
||||
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
|
||||
--- orig/Statistics/Distribution/Gamma.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Gamma.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -226,8 +226,8 @@ diff -ru orig/Statistics/Distribution/Gamma.hs new/Statistics/Distribution/Gamma
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/Geometric.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Geometric.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -272,8 +272,8 @@ diff -ru orig/Statistics/Distribution/Geometric.hs new/Statistics/Distribution/G
|
||||
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
|
||||
--- orig/Statistics/Distribution/Hypergeometric.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Hypergeometric.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -305,26 +305,24 @@ diff -ru orig/Statistics/Distribution/Hypergeometric.hs new/Statistics/Distribut
|
||||
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
|
||||
--- orig/Statistics/Distribution/Normal.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Normal.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -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 @@
|
||||
@@ -28,6 +28,8 @@
|
||||
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 @@
|
||||
@@ -39,7 +41,9 @@
|
||||
, ndCdfDenom :: {-# UNPACK #-} !Double
|
||||
} deriving (Eq, Read, Show, Typeable, Data, Generic)
|
||||
|
||||
@ -336,8 +334,8 @@ diff -ru orig/Statistics/Distribution/Normal.hs new/Statistics/Distribution/Norm
|
||||
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
|
||||
--- orig/Statistics/Distribution/Poisson/Internal.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Poisson/Internal.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -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'
|
||||
@ -357,8 +355,8 @@ diff -ru orig/Statistics/Distribution/Poisson/Internal.hs new/Statistics/Distrib
|
||||
\ 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
|
||||
--- orig/Statistics/Distribution/Poisson.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Poisson.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -400,8 +398,8 @@ diff -ru orig/Statistics/Distribution/Poisson.hs new/Statistics/Distribution/Poi
|
||||
|
||||
-- $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
|
||||
--- orig/Statistics/Distribution/StudentT.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/StudentT.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -430,8 +428,8 @@ diff -ru orig/Statistics/Distribution/StudentT.hs new/Statistics/Distribution/St
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/Transform.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Transform.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts,
|
||||
- FlexibleInstances, UndecidableInstances #-}
|
||||
@ -464,8 +462,8 @@ diff -ru orig/Statistics/Distribution/Transform.hs new/Statistics/Distribution/T
|
||||
-- | 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
|
||||
--- orig/Statistics/Distribution/Uniform.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Distribution/Uniform.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -497,8 +495,8 @@ diff -ru orig/Statistics/Distribution/Uniform.hs new/Statistics/Distribution/Uni
|
||||
-- | 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
|
||||
--- orig/Statistics/Math/RootFinding.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Math/RootFinding.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -540,8 +538,8 @@ diff -ru orig/Statistics/Math/RootFinding.hs new/Statistics/Math/RootFinding.hs
|
||||
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
|
||||
--- orig/Statistics/Resampling/Bootstrap.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Resampling/Bootstrap.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, OverloadedStrings,
|
||||
- RecordWildCards #-}
|
||||
@ -574,8 +572,8 @@ diff -ru orig/Statistics/Resampling/Bootstrap.hs new/Statistics/Resampling/Boots
|
||||
|
||||
-- | 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
|
||||
--- orig/Statistics/Resampling.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Resampling.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric #-}
|
||||
+{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, CPP #-}
|
||||
@ -596,8 +594,8 @@ diff -ru orig/Statistics/Resampling.hs new/Statistics/Resampling.hs
|
||||
-- | /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
|
||||
--- orig/Statistics/Sample/KernelDensity/Simple.hs 2014-04-14 09:04:31.425509375 +0300
|
||||
+++ new/Statistics/Sample/KernelDensity/Simple.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts #-}
|
||||
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts, CPP #-}
|
||||
@ -618,8 +616,8 @@ diff -ru orig/Statistics/Sample/KernelDensity/Simple.hs new/Statistics/Sample/Ke
|
||||
-- | 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
|
||||
--- orig/Statistics/Sample/Powers.hs 2014-04-14 09:04:31.421509375 +0300
|
||||
+++ new/Statistics/Sample/Powers.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric,
|
||||
- FlexibleContexts #-}
|
||||
@ -641,8 +639,8 @@ diff -ru orig/Statistics/Sample/Powers.hs new/Statistics/Sample/Powers.hs
|
||||
-- | 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
|
||||
--- orig/statistics.cabal 2014-04-14 09:04:31.429509375 +0300
|
||||
+++ new/statistics.cabal 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -90,7 +90,7 @@
|
||||
Statistics.Test.Internal
|
||||
build-depends:
|
||||
@ -653,8 +651,8 @@ diff -ru orig/statistics.cabal new/statistics.cabal
|
||||
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
|
||||
--- orig/tests/Tests/Distribution.hs 2014-04-14 09:04:31.425509375 +0300
|
||||
+++ new/tests/Tests/Distribution.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -188,7 +188,7 @@
|
||||
|
||||
-- Quantile is inverse of CDF
|
||||
@ -676,8 +674,8 @@ diff -ru orig/tests/Tests/Distribution.hs new/tests/Tests/Distribution.hs
|
||||
|
||||
|
||||
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
|
||||
--- orig/tests/Tests/Function.hs 2014-04-14 09:04:31.425509375 +0300
|
||||
+++ new/tests/Tests/Function.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -1,7 +1,6 @@
|
||||
module Tests.Function ( tests ) where
|
||||
|
||||
@ -694,8 +692,8 @@ diff -ru orig/tests/Tests/Function.hs new/tests/Tests/Function.hs
|
||||
+ 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
|
||||
--- orig/tests/Tests/Transform.hs 2014-04-14 09:04:31.425509375 +0300
|
||||
+++ new/tests/Tests/Transform.hs 2014-04-14 09:04:31.000000000 +0300
|
||||
@@ -15,7 +15,7 @@
|
||||
import Test.Framework (Test, testGroup)
|
||||
import Test.Framework.Providers.QuickCheck2 (testProperty)
|
||||
|
||||
Loading…
Reference in New Issue
Block a user