#4851: NoImplicitPrelude does not handle rec / mfix / ArrowLoop properly
---------------------------------+------------------------------------------
Reporter: peteg | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.12.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
Consider this program:
{{{
{-# LANGUAGE Arrows, NoImplicitPrelude #-}
module T where
import Prelude hiding ( id, (.) )
import Control.Category ( Category(..) )
import Control.Arrow
garbage =
proc b ->
do rec (c, d) <- undefined -< (b, d)
returnA -< c
}}}
I think this is the new idiomatic way of writing Arrow code due to the use
of Category, which clashes with the Prelude. I wish to avoid the explicit
"import Prelude hiding..." stuff in all the other modules.
In GHC 6.12.3 this gives an error about mfix.
Removing NoImplicitPrelude yields an error about ArrowLoop, as expected.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4851>
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