[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Only use ScopedTypeVariables for GHC (a26fd17)
git at git.haskell.org
git at git.haskell.org
Mon Apr 17 21:41:08 UTC 2017
- Previous message: [commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Merge pull request #236 from treeowl/strictify-seq-splitat (653f597)
- Next message: [commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Merge pull request #233 from treeowl/unscope-nonghc (548b3fa)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
Repository : ssh://git@git.haskell.org/containers
On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link : http://git.haskell.org/packages/containers.git/commitdiff/a26fd17e33eb16caa9331a31f9cad32ad23641c9
>---------------------------------------------------------------
commit a26fd17e33eb16caa9331a31f9cad32ad23641c9
Author: David Feuer <David.Feuer at gmail.com>
Date: Tue May 17 16:58:25 2016 -0400
Only use ScopedTypeVariables for GHC
This isn't (yet) standard, and we don't absolutely need it.
It is nice, however, to be able to give the type signature it
enables, so we can use it when compiling with GHC.
>---------------------------------------------------------------
a26fd17e33eb16caa9331a31f9cad32ad23641c9
Data/IntMap/Base.hs | 8 +++++++-
1 file changed, 7 insertions(+), 1 deletion(-)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index e0a462c..6a4c0dc 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -2,11 +2,11 @@
{-# LANGUAGE BangPatterns #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash, DeriveDataTypeable, StandaloneDeriving #-}
+{-# LANGUAGE ScopedTypeVariables #-}
#endif
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
-{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-}
#endif
@@ -1992,14 +1992,20 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList (combineEq x0 xs0)
--
-- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
+#if __GLASGOW_HASKELL__
fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a
+#else
+fromDistinctAscList :: [(Key,a)] -> IntMap a
+#endif
fromDistinctAscList [] = Nil
fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada
where
work (kx,vx) [] stk = finish kx (Tip kx vx) stk
work (kx,vx) (z@(kz,_):zs) stk = reduce z zs (branchMask kx kz) kx (Tip kx vx) stk
+#if __GLASGOW_HASKELL__
reduce :: (Key,a) -> [(Key,a)] -> Mask -> Prefix -> IntMap a -> Stack a -> IntMap a
+#endif
reduce z zs _ px tx Nada = work z zs (Push px tx Nada)
reduce z zs m px tx stk@(Push py ty stk') =
let mxy = branchMask px py
- Previous message: [commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Merge pull request #236 from treeowl/strictify-seq-splitat (653f597)
- Next message: [commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Merge pull request #233 from treeowl/unscope-nonghc (548b3fa)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
More information about the ghc-commits
mailing list