Hello community,

here is the log from the commit of package ghc-ilist for openSUSE:Factory 
checked in at 2017-08-31 20:56:30
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-ilist (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-ilist.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-ilist"

Thu Aug 31 20:56:30 2017 rev:2 rq:513398 version:0.3.1.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-ilist/ghc-ilist.changes      2017-04-12 
18:07:14.694070606 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-ilist.new/ghc-ilist.changes 2017-08-31 
20:56:31.442906060 +0200
@@ -1,0 +2,5 @@
+Thu Jul 27 14:04:45 UTC 2017 - psim...@suse.com
+
+- Update to version 0.3.1.0.
+
+-------------------------------------------------------------------

Old:
----
  ilist-0.2.0.0.tar.gz

New:
----
  ilist-0.3.1.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-ilist.spec ++++++
--- /var/tmp/diff_new_pack.Hks5hj/_old  2017-08-31 20:56:32.282788054 +0200
+++ /var/tmp/diff_new_pack.Hks5hj/_new  2017-08-31 20:56:32.310784120 +0200
@@ -19,7 +19,7 @@
 %global pkg_name ilist
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.2.0.0
+Version:        0.3.1.0
 Release:        0
 Summary:        Optimised list functions for doing index-related things
 License:        BSD-3-Clause
@@ -36,7 +36,9 @@
 
 %description
 Optimised list functions for doing index-related things. They're faster than
-common idioms in all cases, and sometimes they fuse better as well.
+common idioms in all cases, they avoid
+<https://ghc.haskell.org/trac/ghc/ticket/12620 space leaks>, and sometimes they
+fuse better as well.
 
 %package devel
 Summary:        Haskell %{pkg_name} library development files

++++++ ilist-0.2.0.0.tar.gz -> ilist-0.3.1.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/CHANGELOG.md 
new/ilist-0.3.1.0/CHANGELOG.md
--- old/ilist-0.2.0.0/CHANGELOG.md      2016-05-24 23:12:55.000000000 +0200
+++ new/ilist-0.3.1.0/CHANGELOG.md      2017-06-19 23:55:08.000000000 +0200
@@ -1,3 +1,11 @@
+# 0.3.1.0
+
+* Added `ireplicateM` and `ireplicateM_`.
+
+# 0.3.0.0
+
+* `ifind` now returns the index alongside with the value (same as in `lens`).
+
 # 0.2.0.0
 
 * `izipWithM` and `izipWithM_` have been generalised from `Monad` to 
`Applicative` (which mimics what was done in base-4.9).
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/bench/Functions.hs 
new/ilist-0.3.1.0/bench/Functions.hs
--- old/ilist-0.2.0.0/bench/Functions.hs        2016-05-24 23:12:55.000000000 
+0200
+++ new/ilist-0.3.1.0/bench/Functions.hs        2017-06-19 23:55:08.000000000 
+0200
@@ -1,6 +1,7 @@
 {-# LANGUAGE
 MagicHash,
-BangPatterns
+BangPatterns,
+CPP
   #-}
 
 
@@ -16,6 +17,7 @@
 import Data.List
 import Data.List.Index
 import Control.Monad
+import qualified Control.Loop as Loop
 
 
 indexed_zip :: [a] -> [(Int, a)]
@@ -94,6 +96,20 @@
       go (i +# 1#) xs
 {-# INLINE imapM__rec #-}
 
+#if __GLASGOW_HASKELL__ < 710
+ireplicateM__loop
+  :: (Monad m, Functor m) => Int -> (Int -> m a) -> m ()
+#else
+ireplicateM__loop
+  :: Monad m => Int -> (Int -> m a) -> m ()
+#endif
+ireplicateM__loop n f = Loop.numLoop 0 (n-1) (void . f)
+{-# INLINE ireplicateM__loop #-}
+
+ireplicateM__for :: Monad m => Int -> (Int -> m a) -> m ()
+ireplicateM__for n f = forM_ [0..n-1] f
+{-# INLINE ireplicateM__for #-}
+
 iall_zip :: (Int -> a -> Bool) -> [a] -> Bool
 iall_zip p xs = and (zipWith p [0..] xs)
 {-# INLINE iall_zip #-}
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/bench/Main.hs 
new/ilist-0.3.1.0/bench/Main.hs
--- old/ilist-0.2.0.0/bench/Main.hs     2016-05-24 23:12:55.000000000 +0200
+++ new/ilist-0.3.1.0/bench/Main.hs     2017-06-19 23:55:08.000000000 +0200
@@ -106,6 +106,16 @@
           bench "lens" $ nf (\n -> flip runState [] $ L.imapM_ (\i x -> modify 
((i+x):) >> return (i-x)) [0..n]) 100000,
           bench "our" $ nf (\n -> flip runState [] $ imapM_ (\i x -> modify 
((i+x):) >> return (i-x)) [0..n]) 100000 ] ],
 
+  bgroup "ireplicateM_" [
+      bgroup "Just" [
+          bench "loop" $ nf (\n -> ireplicateM__loop n (\i -> if i<50000 then 
Just i else Nothing)) 100000,
+          bench "for" $ nf (\n -> ireplicateM__for n (\i -> if i<50000 then 
Just i else Nothing)) 100000,
+          bench "our" $ nf (\n -> ireplicateM_ n (\i -> if i<50000 then Just i 
else Nothing)) 100000 ],
+      bgroup "State" [
+          bench "loop" $ nf (\n -> flip runState 0 $ ireplicateM__loop n (\i 
-> modify' (i+))) 100000,
+          bench "for" $ nf (\n -> flip runState 0 $ ireplicateM__for n (\i -> 
modify' (i+))) 100000,
+          bench "our" $ nf (\n -> flip runState 0 $ ireplicateM_ n (\i -> 
modify' (i+))) 100000 ] ],
+
   bgroup "ifilter" [
       bgroup "consume" [
           bench "rec" $ nf (\n -> sum $ ifilter_rec (\i x -> rem (i+x) 5000 == 
0) [0..n]) 100000,
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/ilist.cabal 
new/ilist-0.3.1.0/ilist.cabal
--- old/ilist-0.2.0.0/ilist.cabal       2016-05-24 23:12:55.000000000 +0200
+++ new/ilist-0.3.1.0/ilist.cabal       2017-06-19 23:55:08.000000000 +0200
@@ -1,8 +1,8 @@
 name:                ilist
-version:             0.2.0.0
+version:             0.3.1.0
 synopsis:            Optimised list functions for doing index-related things
 description:
-  Optimised list functions for doing index-related things. They're faster than 
common idioms in all cases, and sometimes they fuse better as well.
+  Optimised list functions for doing index-related things. They're faster than 
common idioms in all cases, they avoid 
<https://ghc.haskell.org/trac/ghc/ticket/12620 space leaks>, and sometimes they 
fuse better as well.
 homepage:            http://github.com/aelve/ilist
 bug-reports:         http://github.com/aelve/ilist/issues
 license:             BSD3
@@ -49,6 +49,7 @@
                      , ilist
                      -- imapM_ is broken in 4.13.2
                      , lens >= 4.13.2.1
+                     , loop
                      , transformers
                      , vector
   ghc-options:         -O2 -Wall -fno-warn-unused-do-bind
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/lib/Data/List/Index.hs 
new/ilist-0.3.1.0/lib/Data/List/Index.hs
--- old/ilist-0.2.0.0/lib/Data/List/Index.hs    2016-05-24 23:12:55.000000000 
+0200
+++ new/ilist-0.3.1.0/lib/Data/List/Index.hs    2017-06-19 23:55:08.000000000 
+0200
@@ -58,6 +58,7 @@
   -- ** Monadic functions
   iforM, iforM_,
   itraverse, itraverse_,
+  ireplicateM, ireplicateM_,
   ifoldrM,
   ifoldlM,
   
@@ -342,6 +343,31 @@
 ifor_ = flip itraverse_
 {-# INLINE ifor_ #-}
 
+{- |
+Perform a given action @n@ times. Behaves like @for_ [0..n-1]@, but avoids 
<https://ghc.haskell.org/trac/ghc/ticket/12620 space leaks>.
+
+If you want more complicated loops (e.g. counting downwards), consider the 
<https://hackage.haskell.org/package/loop loop> package.
+-}
+ireplicateM :: Applicative m => Int -> (Int -> m a) -> m [a]
+ireplicateM cnt f = go 0
+  where
+    go !i | i >= cnt  = pure []
+          | otherwise = (:) <$> f i <*> go (i + 1)
+{-# INLINE ireplicateM #-}
+
+{- |
+NB. This function intentionally uses 'Monad' even though 'Applicative' is 
enough. That's because the @transformers@ package didn't have an optimized 
definition of ('*>') for 'StateT' prior to 0.5.3.0, so for a common case of 
'StateT' this function would be 40 times slower with the 'Applicative' 
constraint.
+-}
+ireplicateM_ :: Monad m => Int -> (Int -> m a) -> m ()
+ireplicateM_ cnt f = if cnt > 0 then go 0 else return ()
+  where
+    -- this is 30% faster for Maybe than the simpler
+    --     go i | i == cnt  = return ()
+    --          | otherwise = f i >> go (i + 1)
+    cnt_ = cnt-1
+    go !i = if i == cnt_ then f i >> return () else f i >> go (i + 1)
+{-# INLINE ireplicateM_ #-}
+
 -- Using unboxed ints here doesn't seem to result in any benefit
 ifoldr :: (Int -> a -> b -> b) -> b -> [a] -> b
 ifoldr f z xs = foldr (\x g i -> f i x (g (i+1))) (const z) xs 0
@@ -493,8 +519,13 @@
 iselect p i x ~(ts,fs) | p i x     = (x:ts,fs)
                        | otherwise = (ts, x:fs)
 
-ifind :: (Int -> a -> Bool) -> [a] -> Maybe a
-ifind p = listToMaybe . ifilter p
+ifind :: (Int -> a -> Bool) -> [a] -> Maybe (Int, a)
+ifind p ls = go 0# ls
+  where
+    go i (x:xs) | p (I# i) x = Just (I# i, x)
+                | otherwise  = go (i +# 1#) xs
+    go _ _ = Nothing
+{-# INLINE ifind #-}
 
 ifindIndex :: (Int -> a -> Bool) -> [a] -> Maybe Int
 ifindIndex p = listToMaybe . ifindIndices p
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/ilist-0.2.0.0/tests/Main.hs 
new/ilist-0.3.1.0/tests/Main.hs
--- old/ilist-0.2.0.0/tests/Main.hs     2016-05-24 23:12:55.000000000 +0200
+++ new/ilist-0.3.1.0/tests/Main.hs     2017-06-19 23:55:08.000000000 +0200
@@ -136,7 +136,7 @@
       specify "basic" $ do
         let f i x = modify ((i,x):) >> return (i-x)
         let (resA, stA) = runState (imapM     f [1,3..9]) []
-        let (resB, stB) = runState (itraverse f [1,3..9]) []
+            (resB, stB) = runState (itraverse f [1,3..9]) []
         resA `shouldBe` [0-1,1-3,2-5,3-7,4-9]
         resB `shouldBe` [0-1,1-3,2-5,3-7,4-9]
         stA `shouldBe` reverse (zip [0..4] [1,3..9])
@@ -154,10 +154,25 @@
       specify "basic" $ do
         let f i x = modify ((i,x):) >> return (i-x)
         let stA = execState (imapM_     f [1,3..9]) []
-        let stB = execState (itraverse_ f [1,3..9]) []
+            stB = execState (itraverse_ f [1,3..9]) []
         stA `shouldBe` reverse (zip [0..4] [1,3..9])
         stB `shouldBe` reverse (zip [0..4] [1,3..9])
 
+  describe "ireplicateM" $ do
+    describe "State" $ do
+      specify "basic" $ do
+        let f i = modify (i:) >> return ((i+1)*2)
+        let (res, st) = runState (ireplicateM 5 f) []
+        res `shouldBe` [2,4..10]
+        st  `shouldBe` reverse [0..4]
+
+  describe "ireplicateM_" $ do
+    describe "State" $ do
+      specify "basic" $ do
+        let f i = modify (i:) >> return ((i+1)*2)
+        let st = execState (ireplicateM_ 5 f) []
+        st `shouldBe` reverse [0..4]
+
 specialFolds :: Spec
 specialFolds = describe "special folds" $ do
   describe "iall" $ do
@@ -245,11 +260,13 @@
 search = describe "search" $ do
   describe "ifind" $ do
     specify "found" $ do
-      ifind (\i x -> i*2==x) [1,3,4,7] `shouldBe` Just 4
+      ifind (\i x -> i*2==x) [1,3,4,7] `shouldBe` Just (2, 4)
+    specify "found twice" $ do
+      ifind (\i x -> i*2==x) [1,3,4,6] `shouldBe` Just (2, 4)
     specify "not found" $ do
       ifind (\i x -> i*2==x) [1,3,5,7] `shouldBe` Nothing
     specify "empty" $ do
-      ifind undefined [] `shouldBe` (Nothing :: Maybe Bool)
+      ifind undefined [] `shouldBe` (Nothing :: Maybe (Int, Bool))
 
   describe "ifindIndex" $ do
     specify "found" $ do


Reply via email to