
#12161: Panic when literal is coerced into function -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: lowest | Milestone: ⊥ Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I don't think there is ever a legitimate use-case for any code which triggers this error, but it does seem to indicate some sort of problem with how ANF Core is defined. Consider: {{{ {-# LANGUAGE MagicHash #-} module G where import GHC.Prim f :: a -> a f = unsafeCoerce# 5# g = case f True of True -> () False -> () }}} When I build this I get: {{{ ezyang@sabre:~$ ghc-8.0 -c G.hs -fforce-recomp ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160204 for x86_64-unknown-linux): CoreToStg.myCollectArgs (5# `cast` (UnsafeCo representational Int# (Bool -> Bool) :: Int# ~R# (Bool -> Bool))) True Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} According to the specification of ANF Core in `CorePrep`, this Core is perfectly legitimate: {{{ Trivial expressions triv ::= lit | var | triv ty | /\a. triv | truv co | /\c. triv | triv |> co Applications app ::= lit | var | app triv | app ty | app co | app |> co Expressions body ::= app | let(rec) x = rhs in body -- Boxed only | case body of pat -> body | /\a. body | /\c. body | body |> co Right hand sides (only place where value lambdas can occur) rhs ::= /\a.rhs | \x.rhs | body }}} as the terminal productions for an `app` include both literals and variables. However, `myCollectArgs` assumes that there are only variables in the function position. So it seems that in practice we need a stronger invariant on ANF. An obvious fix is to remove `lit` from `app`, but that is not quite enough because then there is no way to represent expressions of the form `let x = lit in body` (in particular, `MachStr` and `LitInteger` are not considered trivial and may very well be let-bound). So perhaps the right way to do this is to remove `lit` from `app`, and add it to `body`: {{{ Trivial expressions triv ::= lit | var | triv ty | /\a. triv | truv co | /\c. triv | triv |> co Applications (removed lit) app ::= var | app triv | app ty | app co | app |> co Expressions (added lit) body ::= app | lit | let(rec) x = rhs in body -- Boxed only | case body of pat -> body | /\a. body | /\c. body | body |> co Right hand sides (only place where value lambdas can occur) rhs ::= /\a.rhs | \x.rhs | body }}} the point being that we never have an application with a literal in function position. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12161 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler