[commit: packages/base] ghc-7.8: Fix build due to missing scanl' (416ef66)
git at git.haskell.org
git at git.haskell.org
Wed Nov 5 22:45:21 UTC 2014
Repository : ssh://git@git.haskell.org/base
On branch : ghc-7.8
Link : http://ghc.haskell.org/trac/ghc/changeset/416ef6644ca26ecbebc8dfa5af1963e47e0b2e06/base
>---------------------------------------------------------------
commit 416ef6644ca26ecbebc8dfa5af1963e47e0b2e06
Author: Austin Seipp <austin at well-typed.com>
Date: Wed Nov 5 16:07:08 2014 -0600
Fix build due to missing scanl'
This was sitting in my working tree, and I forgot to commit it. Oops.
This is not exported by Data.List, since it's only needed by 'inits'
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
416ef6644ca26ecbebc8dfa5af1963e47e0b2e06
Data/List.hs | 15 ++++++++++++++-
1 file changed, 14 insertions(+), 1 deletion(-)
diff --git a/Data/List.hs b/Data/List.hs
index 8973464..0b484e0 100644
--- a/Data/List.hs
+++ b/Data/List.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, BangPatterns #-}
-----------------------------------------------------------------------------
-- |
@@ -754,10 +754,23 @@ groupBy eq (x:xs) = (x:ys) : groupBy eq zs
inits :: [a] -> [[a]]
inits = map toListSB . scanl' snocSB emptySB
{-# NOINLINE inits #-}
+
-- We do not allow inits to inline, because it plays havoc with Call Arity
-- if it fuses with a consumer, and it would generally lead to serious
-- loss of sharing if allowed to fuse with a producer.
+-- | A strictly accumulating version of 'scanl'
+{-# NOINLINE [1] scanl' #-}
+scanl' :: (b -> a -> b) -> b -> [a] -> [b]
+-- This peculiar form is needed to prevent scanl' from being rewritten
+-- in its own right hand side.
+scanl' = scanlGo'
+ where
+ scanlGo' :: (b -> a -> b) -> b -> [a] -> [b]
+ scanlGo' f !q ls = q : (case ls of
+ [] -> []
+ x:xs -> scanlGo' f (f q x) xs)
+
-- | The 'tails' function returns all final segments of the argument,
-- longest first. For example,
--
More information about the ghc-commits
mailing list