#5283: Arrow command combinators: addTickHsExpr explodes in GHCi
---------------------------------+------------------------------------------
    Reporter:  peteg             |       Owner:                    
        Type:  bug               |      Status:  new               
    Priority:  normal            |   Component:  Compiler          
     Version:  7.0.3             |    Keywords:                    
    Testcase:                    |   Blockedby:                    
          Os:  Unknown/Multiple  |    Blocking:                    
Architecture:  Unknown/Multiple  |     Failure:  Compile-time crash
---------------------------------+------------------------------------------
 This code:

 {{{
 {-# LANGUAGE Arrows #-}
 module T where

 import Prelude
 import Control.Arrow

 mapAC :: Arrow arr => Integer -> arr (env, b) c -> arr (env, [b]) [c]
 mapAC n farr = go 1
   where
     go i | i == succ n = arr (\(_env, []) -> [])
          | otherwise = proc ~(env, b : bs) ->
              do c  <- farr -< (env, b)
                 cs <- go (succ i) -< (env, bs)
                 returnA -< c : cs

 t :: Arrow arr => arr [a] [a]
 t = proc ys ->
      (| (mapAC 3) (\y -> returnA -< y) |) ys
 }}}

 compiles fine using GHC. In GHCi I get:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.0.3 for i386-apple-darwin):
         addTickHsExpr
     (|/\(@ a{tv ar3} [sk]).
       ((main:T.mapAC{v rdR} [lid]) @ arr{tv aqZ} [sk] @ a{tv ar3} [sk]
        @ a{tv ar0} [sk]
        @ a{tv ar0} [sk]
          $dArrow{v ar4} [lid]
          3 (3))
         ((\ ((y{v ajL} [lid] :: a{tv ar0} [sk]))
             -> {18:26-37}
                (base:Control.Arrow.returnA{v rdx} [gid]) @ arr{tv aqZ}
 [sk]
                @ a{tv ar0} [sk]
                  $dArrow{v ar5} [lid] -< y{v ajL} [lid]))|)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5283>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to