[GHC] #16141: StrictData and TypeFamilies regression
GHC
ghc-devs at haskell.org
Mon Jan 7 14:27:40 UTC 2019
#16141: StrictData and TypeFamilies regression
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.6.3
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
It turns out you don't need `deriving` to notice something afoot with this
program. Even if you just have this:
{{{#!hs
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where
data family T
newtype instance T = MkT Int
}}}
And compile this with `-O -dcore-lint`, it blows up:
{{{
$ /opt/ghc/8.6.3/bin/ghc Bug.hs -O -dcore-lint
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
*** Core Lint errors : in result of Tidy Core ***
<no location info>: warning:
In a case alternative: (I# dt_aXp :: Int#)
Type of case alternatives not the same as the annotation on case:
Actual type: R:T
Annotation on case: T
Alt Rhs: dt_aXp `cast` (Sym (N:R:T[0]) :: Int# ~R# R:T)
*** Offending Program ***
$WMkT [InlPrag=INLINE[2]] :: Int -> T
[GblId[DataConWrapper],
Arity=1,
Caf=NoCafRefs,
Str=<S,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (dt_aXo [Occ=Once!] :: Int) ->
(case dt_aXo of { I# dt_aXp [Occ=Once] ->
dt_aXp `cast` (Sym (N:R:T[0]) :: Int# ~R# R:T)
})
`cast` (Sym (D:R:T0[0]) :: R:T ~R# T)}]
$WMkT
= \ (dt_aXo [Occ=Once!] :: Int) ->
(case dt_aXo of { I# dt_aXp [Occ=Once] ->
dt_aXp `cast` (Sym (N:R:T[0]) :: Int# ~R# R:T)
})
`cast` (Sym (D:R:T0[0]) :: R:T ~R# T)
<elided>
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16141#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list