#5333: Arrow command combinators and infixr cause the desugarer to fail ---------------------------------+------------------------------------------ Reporter: peteg | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Parser) Version: 7.0.3 | Keywords: Testcase: | Blockedby: Os: Unknown/Multiple | Blocking: Architecture: Unknown/Multiple | Failure: GHC rejects valid program ---------------------------------+------------------------------------------ The following code exhibits the bug:
{{{ {-# LANGUAGE Arrows, NoMonomorphismRestriction #-} module T where import Prelude hiding ( id, (.) ) import Control.Arrow cc1 :: Arrow a => a e b -> a e b -> a e b cc1 = undefined -- 'g' fails to compile. -- g = proc (x, y, z) -> -- ((returnA -< x) &&& (returnA -< y) &&& (returnA -< z)) -- 'f' compiles: -- - without an infix declaration -- - with the infixl declaration -- and fails with the infixr declaration infixr 6 `cc1` -- infixl 6 `cc1` f = proc (x, y, z) -> ((returnA -< x) `cc1` (returnA -< y) `cc1` (returnA -< z)) }}} GHC says: {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.0.3 for i386-apple-darwin): dsSyntaxTable Not found: base:GHC.Desugar.>>>{v 01W} }}} -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5333> 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