[commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use coerce for [a]->[Elem a] convertion in fromList. (9b37d5a)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 22:10:23 UTC 2015
Repository : ssh://git@git.haskell.org/containers
On branches: develop-0.6,develop-0.6-questionable,master
Link : http://git.haskell.org/packages/containers.git/commitdiff/9b37d5a262e8070abce1f51d4913d9312a630acd
>---------------------------------------------------------------
commit 9b37d5a262e8070abce1f51d4913d9312a630acd
Author: Milan Straka <fox at ucw.cz>
Date: Mon Dec 15 17:37:18 2014 +0100
Use coerce for [a]->[Elem a] convertion in fromList.
>---------------------------------------------------------------
9b37d5a262e8070abce1f51d4913d9312a630acd
Data/Sequence.hs | 10 +++++++++-
1 file changed, 9 insertions(+), 1 deletion(-)
diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 1b6dea2..71ded95 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -1759,7 +1759,7 @@ findIndicesR p xs = foldlWithIndex g [] xs
-- There is a function 'toList' in the opposite direction for all
-- instances of the 'Foldable' class, including 'Seq'.
fromList :: [a] -> Seq a
-fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs
+fromList xs = Seq $ mkTree 1 $ map_elem xs
where
{-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-}
{-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-}
@@ -1781,6 +1781,14 @@ fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs
getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d)
where (ns, d) = getNodes s xs
+ map_elem :: [a] -> [Elem a]
+#if __GLASGOW_HASKELL__ >= 708
+ map_elem xs = coerce xs
+#else
+ map_elem xs = Data.List.map Elem xs
+#endif
+ {-# INLINE map_elem #-}
+
#if __GLASGOW_HASKELL__ >= 708
instance GHC.Exts.IsList (Seq a) where
type Item (Seq a) = a
More information about the ghc-commits
mailing list