#1662: mistranslation of arrow notation
-------------------------------------+--------------------------------------
 Reporter:  ross                     |          Owner:  igloo   
     Type:  bug                      |         Status:  reopened
 Priority:  normal                   |      Milestone:          
Component:  Compiler (Type checker)  |        Version:  6.8.1   
 Severity:  normal                   |     Resolution:          
 Keywords:                           |     Difficulty:  Unknown 
 Testcase:  arrowrun004, arrowpat    |   Architecture:  Multiple
       Os:  Multiple                 |  
-------------------------------------+--------------------------------------
Changes (by guest):

  * status:  closed => reopened
  * type:  merge => bug
  * version:  6.7 => 6.8.1
  * resolution:  fixed =>
  * milestone:  6.8.1 =>

Comment:

 As I understand the above {{{TcPat}}} comment, the compiler should not
 accept {{{proc}}} expressions with existential constraints.  Therefore, I
 would expect GHC 6.8.1 to fail on the following code:
 {{{
 {-# LANGUAGE Arrows, ExistentialQuantification #-}
 module ANewPanicWithArrows where

     import Control.Arrow

     data T = forall a. T a

     panic :: (Arrow arrow) => arrow T T
     panic = proc (T x) -> do returnA -< T x
 }}}
 However, as the code suggests, GHC doesn’t fail but panics again:
 {{{
 ghc-6.8.1: panic! (the 'impossible' happened)
   (GHC version 6.8.1 for i386-unknown-linux):
         initC: srt_lbl
 }}}
 If I load the module into GHCi, GHCi doesn’t complain, but it panics with
 {{{nameModule arr{v apv}}}} (instead of {{{initC: srt_lbl}}}) when I start
 to use the {{{panic}}} arrow.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1662#comment:10>
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