core lint error with arrow notation and GADTs
The following code panics GHC (with 7.0.3, 7.2 and 7.4.0.20111219):
{-# 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 -< ()
-- arrif = arr (\BoolVal -> ())
I am attaching the -dcore-lint from 7.4.
Trac metadata
Trac field | Value |
---|---|
Version | 7.4.1-rc1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | ben@moseley.name, benjamin.moseley@barclayscapital.com |
Operating system | MacOS X |
Architecture | x86 |
- Show closed items
Relates to
- #135475
Related merge requests 1
When this merge request is accepted, this issue will be closed automatically.
Activity
-
Newest first Oldest first
-
Show all activity Show comments only Show history only
- benmos changed weight to 5
changed weight to 5
- benmos added GADTs Tbug Trac import labels
added GADTs Tbug Trac import labels
- Author
Attached file
arrow-gadt-panic.txt
(download).Core Lint output
- Author
Attached file
Test3.hs
($655).Source file
- Ross Paterson changed title from Panic with Arrow Notation and GADTs to core lint error with arrow notation and GADTs
changed title from Panic with Arrow Notation and GADTs to core lint error with arrow notation and GADTs
- Developer
Simplified version, avoiding classes:
{-# LANGUAGE Arrows, GADTs #-} module ArrowBug5777 where import Control.Arrow data Value a where BoolVal :: Value Bool arrif :: Value Bool -> () arrif = proc BoolVal -> returnA -< ()
- Author
The workaround is to move the GADT data constructor out of the 'proc' pattern and into a 'let':
data Value a where BoolVal :: Int -> Value Bool arrif :: Value Bool -> Int arrif = proc x -> do let BoolVal i = x returnA -< i
- Ian Lynagh <igloo@earth.li> changed milestone to %7.4.2
changed milestone to %7.4.2
- Ian Lynagh <igloo@earth.li> changed milestone to %7.4.3
changed milestone to %7.4.3
- Simon Peyton Jones mentioned in issue #7071 (closed)
mentioned in issue #7071 (closed)
- Ian Lynagh <igloo@earth.li> changed milestone to %7.6.2
changed milestone to %7.6.2
This also happens on GHC 7.4.2 x86_64.
$ ghc --make Test3.hs [1 of 1] Compiling Main ( Test3.hs, Test3.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.4.2 for x86_64-apple-darwin): cgLookupPanic (probably invalid Core; try -dcore-lint) ( $dArrow{v amL} [lid] :: base:Control.Arrow.Arrow{tc r4n} ghc-prim:GHC.Prim.(->){(w) tc 3D} ) static binds for: local binds for: ( main:Main.arrif{v rci} [gid[ClassOp]] :: forall (( f{tv acm} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} -> ghc-prim:GHC.Prim.*{(w) tc 34d} ) :: ghc-prim:GHC.Prim.*{(w) tc 34d} -> ghc-prim:GHC.Prim.*{(w) tc 34d}). main:Main.ArrowInit{tc rch} ( f{tv acm} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} -> ghc-prim:GHC.Prim.*{(w) tc 34d} ) => forall ( b{tv acn} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} ). ( f{tv acm} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} -> ghc-prim:GHC.Prim.*{(w) tc 34d} ) ( b{tv acn} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} ) -> ghc-prim:GHC.Tuple.(){(w) tc 40} ) ( main:Main.$WBoolVal{v rcH} [gid[DataConWrapper]] :: main:Main.Value{tc rcj} ghc-prim:GHC.Types.Bool{(w) tc 3c} ) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Trac metadata
Trac field Value Version 7.4.1-rc1 → 7.4.2 Architecture x86 → Unknown/Multiple - Developer
Ross, do you feel able to help with this. I have no clue.
Trac metadata
Trac field Value CC abcz2.uprola@gmail.com, ben@moseley.name, benjamin.moseley@barclayscapital.com → abcz2.uprola@gmail.com, ben@moseley.name, benjamin.moseley@barclayscapital.com, ross - Ross Paterson assigned to @trac-ross
assigned to @trac-ross
- Developer
I'll put it on my list, but first priority is ArrForm (#5267/#5609 (closed)), followed by infixr (#5333 (closed)), with this and #344 (closed) as the lowest.
- Simon Peyton Jones mentioned in commit c3ad38d7
mentioned in commit c3ad38d7
- thoughtpolice changed milestone to %7.10.1
changed milestone to %7.10.1
Moving to 7.10.1.
Bug still present in HEAD (ghc-7.9.20141125).
Trac metadata
Trac field Value Component Compiler → Compiler (Type checker) Operating system MacOS X → Unknown/Multiple - thoughtpolice removed milestone
removed milestone
Moving to 7.12.1 milestone; if you feel this is an error and should be addressed sooner, please move it back to the 7.10.1 milestone.
- Simon Peyton Jones mentioned in issue #9985 (closed)
mentioned in issue #9985 (closed)
- thoughtpolice changed milestone to %8.0.1
changed milestone to %8.0.1
Milestone renamed
- Thomas Miedema added Arrows label and removed GADTs label
- Ryan Scott mentioned in issue #13547
mentioned in issue #13547
- Maintainer
Trac metadata
Trac field Value Related - → #13547 - Ryan Scott mentioned in issue #15175 (closed)
mentioned in issue #15175 (closed)
- Maintainer
Trac metadata
Trac field Value Related #13547 → #13547, #15175 (closed) - trac-import added GADTs label
added GADTs label
- trac-import added compiler crash label
added compiler crash label
- Ben Gamari added Pnormal label
added Pnormal label
- JustMoi mentioned in issue #18950 (closed)
mentioned in issue #18950 (closed)
- Krzysztof Gogolewski mentioned in commit 4b574938
mentioned in commit 4b574938
- Krzysztof Gogolewski mentioned in merge request !4957 (closed)
mentioned in merge request !4957 (closed)