[GHC] #16141: StrictData and TypeFamilies regression
GHC
ghc-devs at haskell.org
Mon Jan 7 17:24:25 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):
I'm starting to think that this is actually an old bug with `StrictData`,
since the following program (which uses a plain old newtype, not a data
family) also breaks Core Lint in a similar fashion with GHC 8.4.4 or
later:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
module Bug where
newtype T a b where
MkT :: forall b a. Int -> T a b
}}}
{{{
$ /opt/ghc/8.4.4/bin/ghc -O -dcore-lint Bug.hs
[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_aXx :: Int#)
Type of case alternatives not the same as the annotation on case:
Actual type: T a_atk b_atj
Annotation on case: T b_atj a_atk
Alt Rhs: dt_aXx
`cast` (Sym (N:T[0] <a_atk>_P <b_atj>_P)
:: (Int# :: TYPE 'IntRep) ~R# (T a_atk b_atj ::
*))
*** Offending Program ***
$WMkT [InlPrag=INLINE[2]] :: forall b a. Int -> T a b
[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= \ (@ b_atj) (@ a_atk) (dt_aXw [Occ=Once!] :: Int) ->
case dt_aXw of { I# dt_aXx [Occ=Once] ->
dt_aXx
`cast` (Sym (N:T[0] <a_atk>_P <b_atj>_P)
:: (Int# :: TYPE 'IntRep) ~R# (T a_atk b_atj ::
*))
}}]
$WMkT
= \ (@ b_atj) (@ a_atk) (dt_aXw [Occ=Once!] :: Int) ->
case dt_aXw of { I# dt_aXx [Occ=Once] ->
dt_aXx
`cast` (Sym (N:T[0] <a_atk>_P <b_atj>_P)
:: (Int# :: TYPE 'IntRep) ~R# (T a_atk b_atj :: *))
}
<elided>
}}}
The issue appears to involve newtypes with wrappers in general. (The
reason why the original program only started breaking with GHC 8.6 is
because commit eb680f2c0a365b12f9b867da6bb10e9ab4b328e0 changed GHC's
treatment of newtype instances so that they would have wrappers where they
didn't before.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16141#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list