[commit: packages/vector] ghc-head: Work around bug in ghc-7.6.1 (b3114f2)

git at git.haskell.org git at git.haskell.org
Thu Sep 26 11:54:18 CEST 2013


Repository : ssh://git@git.haskell.org/vector

On branch  : ghc-head
Link       : http://git.haskell.org/packages/vector.git/commitdiff/b3114f2354c5bf5474541ae487802618a00dbe2f

>---------------------------------------------------------------

commit b3114f2354c5bf5474541ae487802618a00dbe2f
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date:   Fri Sep 28 23:10:21 2012 +0000

    Work around bug in ghc-7.6.1


>---------------------------------------------------------------

b3114f2354c5bf5474541ae487802618a00dbe2f
 Data/Vector/Fusion/Stream/Monadic.hs |    5 +++--
 1 file changed, 3 insertions(+), 2 deletions(-)

diff --git a/Data/Vector/Fusion/Stream/Monadic.hs b/Data/Vector/Fusion/Stream/Monadic.hs
index c77bceb..5f1c363 100644
--- a/Data/Vector/Fusion/Stream/Monadic.hs
+++ b/Data/Vector/Fusion/Stream/Monadic.hs
@@ -1683,7 +1683,7 @@ fromVector v = v `seq` n `seq` Facets (Unf step 0)
     vstep True  = return (Yield (Chunk (basicLength v) (\mv -> basicUnsafeCopy mv v)) False)
     vstep False = return Done
 
-fromVectors :: (Monad m, Vector v a) => [v a] -> Facets m v a
+fromVectors :: forall m v a. (Monad m, Vector v a) => [v a] -> Facets m v a
 {-# INLINE_FUSED fromVectors #-}
 fromVectors vs = Facets (Unf pstep (Left vs))
                         (Unf vstep vs)
@@ -1700,7 +1700,8 @@ fromVectors vs = Facets (Unf pstep (Left vs))
       | otherwise          = case basicUnsafeIndexM v i of
                                Box x -> return $ Yield x (Right (v,i+1,vs))
 
-
+    -- FIXME: work around bug in GHC 7.6.1
+    vstep :: [v a] -> m (Step [v a] (Chunk v a))
     vstep [] = return Done
     vstep (v:vs) = return $ Yield (Chunk (basicLength v)
                                          (\mv -> basicUnsafeCopy mv v)) vs




More information about the ghc-commits mailing list