#4350: Compiler crash building latest binary package in hackage with 7.0.1-rc1
-----------------------+----------------------------------------------------
    Reporter:  dsf     |       Owner:                    
        Type:  bug     |      Status:  new               
    Priority:  normal  |   Component:  Compiler          
     Version:  7.1     |    Keywords:                    
    Testcase:          |   Blockedby:                    
          Os:  Linux   |    Blocking:                    
Architecture:  x86     |     Failure:  Compile-time crash
-----------------------+----------------------------------------------------
 My understanding is that the binary package should now be provided
 separately from the ghc-binary package.  Unfortunately, it does not
 currently compile:

 {{{
 src/Data/Binary/Get.hs:366:27:
     Couldn't match type `s' with `s1'
       because this skolem type variable would escape: `s1'
     This skolem is bound by the polymorphic type `forall s. ST s a'
     The following variables have types that mention s
       first :: STRef s L.ByteString
                -> Int64
                -> L.ByteString
                -> ST s L.ByteString
         (bound at src/Data/Binary/Get.hs:373:9)
     In the first argument of `runST', namely
       `(do { r <- newSTRef undefined;
              xs <- first r i ps;
              ys <- unsafeInterleaveST (readSTRef r);
              return (xs, ys) })'
     In the expression:
       runST
         (do { r <- newSTRef undefined;
               xs <- first r i ps;
               ys <- unsafeInterleaveST (readSTRef r);
               return (xs, ys) })
     In an equation for `splitAtST':
         splitAtST i ps
           = runST
               (do { r <- newSTRef undefined;
                     xs <- first r i ps;
                     ys <- unsafeInterleaveST (readSTRef r);
                     return (xs, ys) })
           where
               first r 0 xs@(L.Chunk _ _) = writeSTRef r xs >> return
 L.Empty
               first r _ L.Empty = writeSTRef r L.Empty >> return L.Empty
               first r n (L.Chunk x xs)
                 | n < l
                 = do { writeSTRef r (L.Chunk (B.drop (fromIntegral n) x)
 xs);
                        .... }
                 | otherwise
                 = do { writeSTRef r (L.drop (n - l) xs);
                        .... }
                 where
                     l = fromIntegral (B.length x)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4350>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to