Arrow Notation / GADT panic (GHC Trac #5777)
Ben Moseley
ben_moseley at mac.com
Sun Jan 15 17:18:04 CET 2012
The following code seems to trigger a panic (under 7.03, 7.2 and 7.4):
{-# LANGUAGE Arrows, GADTs #-}
import Control.Arrow
data Value a where BoolVal :: Value Bool
class ArrowInit f where
arrif :: f b -> ()
instance ArrowInit Value where
arrif = proc BoolVal -> returnA -< () -- this panics
-- arrif = arr (\BoolVal -> ()) -- this works
I've filed this as: http://hackage.haskell.org/trac/ghc/ticket/5777
--Ben
More information about the Glasgow-haskell-users
mailing list