Script 'mail_helper' called by obssrc
Hello community,
here is the log from the commit of package ghc-statistics for openSUSE:Factory checked in at 2023-09-28 00:26:17
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-statistics (Old)
and /work/SRC/openSUSE:Factory/.ghc-statistics.new.23327 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-statistics"
Thu Sep 28 00:26:17 2023 rev:9 rq:1113898 version:0.16.2.1
Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-statistics/ghc-statistics.changes 2023-04-14 13:13:00.167538008 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-statistics.new.23327/ghc-statistics.changes 2023-09-28 00:33:42.582462961 +0200
@@ -1,0 +2,10 @@
+Thu Sep 21 18:43:54 UTC 2023 - Peter Simons <psimons(a)suse.com>
+
+- Update statistics to version 0.16.2.1.
+ ## Changes in 0.16.2.1
+
+ * Unnecessary constraint dropped from `tStatisticsPaired`.
+
+ * Compatibility with QuickCheck-2.14. Test suite doesn't fail every time.
+
+-------------------------------------------------------------------
Old:
----
statistics-0.16.2.0.tar.gz
New:
----
statistics-0.16.2.1.tar.gz
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Other differences:
------------------
++++++ ghc-statistics.spec ++++++
--- /var/tmp/diff_new_pack.TBZL5W/_old 2023-09-28 00:33:43.630500790 +0200
+++ /var/tmp/diff_new_pack.TBZL5W/_new 2023-09-28 00:33:43.630500790 +0200
@@ -20,7 +20,7 @@
%global pkgver %{pkg_name}-%{version}
%bcond_with tests
Name: ghc-%{pkg_name}
-Version: 0.16.2.0
+Version: 0.16.2.1
Release: 0
Summary: A library of statistical types, data, and functions
License: BSD-2-Clause
++++++ statistics-0.16.2.0.tar.gz -> statistics-0.16.2.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/Statistics/Test/StudentT.hs new/statistics-0.16.2.1/Statistics/Test/StudentT.hs
--- old/statistics-0.16.2.0/Statistics/Test/StudentT.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/Statistics/Test/StudentT.hs 2001-09-09 03:46:40.000000000 +0200
@@ -134,16 +134,16 @@
-- Calculate T-statistics for paired sample
-tStatisticsPaired :: (G.Vector v (Double, Double), G.Vector v Double)
+tStatisticsPaired :: (G.Vector v (Double, Double))
=> v (Double, Double)
-> (Double, Double)
{-# INLINE tStatisticsPaired #-}
tStatisticsPaired sample = (t, ndf)
where
-- t-statistics
- t = let d = G.map (uncurry (-)) sample
- sumd = G.sum d
- in sumd / sqrt ((n * G.sum (G.map square d) - square sumd) / ndf)
+ t = let d = U.map (uncurry (-)) $ G.convert sample
+ sumd = U.sum d
+ in sumd / sqrt ((n * U.sum (U.map square d) - square sumd) / ndf)
-- degree of freedom
ndf = n - 1
n = fromIntegral $ G.length sample
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/changelog.md new/statistics-0.16.2.1/changelog.md
--- old/statistics-0.16.2.0/changelog.md 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/changelog.md 2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,10 @@
+## Changes in 0.16.2.1
+
+ * Unnecessary constraint dropped from `tStatisticsPaired`.
+
+ * Compatibility with QuickCheck-2.14. Test suite doesn't fail every time.
+
+
## Changes in 0.16.2.0
* Improved precision for `complCumulative` for hypergeometric and binomial
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/statistics.cabal new/statistics-0.16.2.1/statistics.cabal
--- old/statistics-0.16.2.0/statistics.cabal 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/statistics.cabal 2001-09-09 03:46:40.000000000 +0200
@@ -1,5 +1,5 @@
name: statistics
-version: 0.16.2.0
+version: 0.16.2.1
synopsis: A library of statistical types, data, and functions
description:
This library provides a number of common functions and types useful
@@ -46,14 +46,15 @@
tests/utils/fftw.c
tested-with:
- GHC ==8.0.2
- || ==8.2.2
- || ==8.4.4
- || ==8.6.5
- || ==8.8.4
- || ==8.10.7
- || ==9.0.1
- || ==9.2.1
+ GHC ==8.4.4
+ GHC ==8.6.5
+ GHC ==8.8.4
+ GHC ==8.10.7
+ GHC ==9.0.2
+ GHC ==9.2.8
+ GHC ==9.4.6
+ GHC ==9.6.2
+
library
default-language: Haskell2010
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/tests/Tests/Correlation.hs new/statistics-0.16.2.1/tests/Tests/Correlation.hs
--- old/statistics-0.16.2.0/tests/Tests/Correlation.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/tests/Tests/Correlation.hs 2001-09-09 03:46:40.000000000 +0200
@@ -5,11 +5,11 @@
import Control.Arrow (Arrow(..))
import qualified Data.Vector as V
+import Data.Maybe
import Statistics.Correlation
import Statistics.Correlation.Kendall
-import Test.QuickCheck ((==>),Property,counterexample)
import Test.Tasty
-import Test.Tasty.QuickCheck
+import Test.Tasty.QuickCheck hiding (sample)
import Test.Tasty.HUnit
import Tests.ApproxEq
@@ -34,15 +34,19 @@
testPearson :: [(Double,Double)] -> Property
testPearson sample
- = (length sample > 1) ==> (exact ~= fast)
+ = (length sample > 1 && isJust exact) ==> (case exact of
+ Just e -> e ~= fast
+ Nothing -> property False
+ )
where
(~=) = eql 1e-12
exact = exactPearson $ map (realToFrac *** realToFrac) sample
fast = pearson $ V.fromList sample
-exactPearson :: [(Rational,Rational)] -> Double
+exactPearson :: [(Rational,Rational)] -> Maybe Double
exactPearson sample
- = realToFrac cov / sqrt (realToFrac (varX * varY))
+ | varX == 0 || varY == 0 = Nothing
+ | otherwise = Just $ realToFrac cov / sqrt (realToFrac (varX * varY))
where
(xs,ys) = unzip sample
n = fromIntegral $ length sample
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/tests/Tests/Distribution.hs new/statistics-0.16.2.1/tests/Tests/Distribution.hs
--- old/statistics-0.16.2.0/tests/Tests/Distribution.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/tests/Tests/Distribution.hs 2001-09-09 03:46:40.000000000 +0200
@@ -348,7 +348,7 @@
quantileIsInvCDF_enabled _ = False
-- We compute CDF and complement using same method so precision
-- should be very good here.
- prec_complementCDF _ = 2 * m_epsilon
+ prec_complementCDF _ = 64 * m_epsilon
instance Param ChiSquared where
prec_quantile_CDF _ = (32,32)
@@ -367,7 +367,7 @@
-- introduced by exp . logGamma. This could only be fixed in
-- math-function by implementing gamma
prec_quantile_CDF _ = (24,24)
- prec_logDensity _ = 64
+ prec_logDensity _ = 512
instance Param GeometricDistribution
instance Param GeometricDistribution0
instance Param HypergeometricDistribution
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/tests/Tests/Matrix/Types.hs new/statistics-0.16.2.1/tests/Tests/Matrix/Types.hs
--- old/statistics-0.16.2.0/tests/Tests/Matrix/Types.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/tests/Tests/Matrix/Types.hs 2001-09-09 03:46:40.000000000 +0200
@@ -6,6 +6,8 @@
Mat(..)
, fromMat
, toMat
+ , arbMat
+ , arbMatWith
) where
import Control.Monad (join)
@@ -32,10 +34,21 @@
arbitrary = small $ join (arbMat <$> arbitrary <*> arbitrary)
shrink (Mat r c xs) = Mat r c <$> shrinkFixedList (shrinkFixedList shrink) xs
-arbMat :: (Arbitrary a) => Positive (Small Int) -> Positive (Small Int)
- -> Gen (Mat a)
-arbMat (Positive (Small r)) (Positive (Small c)) =
- Mat r c <$> vectorOf r (vector c)
+arbMat
+ :: (Arbitrary a)
+ => Positive (Small Int)
+ -> Positive (Small Int)
+ -> Gen (Mat a)
+arbMat r c = arbMatWith r c arbitrary
+
+arbMatWith
+ :: (Arbitrary a)
+ => Positive (Small Int)
+ -> Positive (Small Int)
+ -> Gen a
+ -> Gen (Mat a)
+arbMatWith (Positive (Small r)) (Positive (Small c)) genA =
+ Mat r c <$> vectorOf r (vectorOf c genA)
instance Arbitrary Matrix where
arbitrary = fromMat <$> arbitrary
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/statistics-0.16.2.0/tests/Tests/Matrix.hs new/statistics-0.16.2.1/tests/Tests/Matrix.hs
--- old/statistics-0.16.2.0/tests/Tests/Matrix.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/statistics-0.16.2.1/tests/Tests/Matrix.hs 2001-09-09 03:46:40.000000000 +0200
@@ -5,7 +5,6 @@
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.QuickCheck (testProperty)
import Test.QuickCheck
-import Tests.ApproxEq (ApproxEq(..))
import Tests.Matrix.Types
import qualified Data.Vector.Unboxed as U
@@ -27,9 +26,20 @@
t_transpose m = U.concat (map (column n) [0..rows m-1]) === toVector m
where n = transpose m
-t_qr :: Matrix -> Property
-t_qr a = hasNaN p .||. eql 1e-10 a p
- where p = uncurry multiply (qr a)
+t_qr :: Property
+t_qr = property $ do
+ a <- do (r,c) <- arbitrary
+ fromMat <$> arbMatWith r c (fromIntegral <$> choose (-10, 10::Int))
+ let (q,r) = qr a
+ a' = multiply q r
+ pure $ counterexample ("A = \n"++show a)
+ $ counterexample ("A' = \n"++show a')
+ $ counterexample ("Q = \n"++show q)
+ $ counterexample ("R = \n"++show r)
+ $ dimension a == dimension a'
+ && ( hasNaN a'
+ || and (zipWith (\x y -> abs (x - y) < 1e-12) (toList a) (toList a'))
+ )
tests :: TestTree
tests = testGroup "Matrix"