#5038: internal error with rebindable if-then-else
-------------------------------+--------------------------------------------
    Reporter:  Philonous       |       Owner:              
        Type:  bug             |      Status:  new         
    Priority:  normal          |   Component:  Compiler    
     Version:  7.0.2           |    Keywords:              
    Testcase:                  |   Blockedby:              
          Os:  Linux           |    Blocking:              
Architecture:  x86_64 (amd64)  |     Failure:  None/Unknown
-------------------------------+--------------------------------------------
 Defining ifThenElse in a module with RebindableSyntax enabled and using
 if-then-else in the same module leads to an internal ghc error.


 ifThenElse.hs:
 {{{
 {-# LANGUAGE RebindableSyntax #-}

 module IfThenElse (ifThenElse) where

 import Prelude (Bool(..))

 ifThenElse True t f = t
 ifThenElse False t f = f

 foo = if True then () else ()
 }}}

 Error message:

 {{{

 # ghc IfThenElse.hs
 [1 of 1] Compiling IfThenElse       ( IfThenElse.hs, IfThenElse.o )

 IfThenElse.hs:10:7:
     GHC internal error: `ifThenElse' is not in scope during type checking,
 but it passed the renamer
     tcg_type_env of environment: []
     tcl_env of environment: []
     In the expression: if True then () else ()
     In an equation for `foo': foo = if True then () else ()
 }}}

 Importing ifThenElse from another module (even with RebindableSyntax
 enabled) will make the error go away.

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