[GHC] #16141: StrictData and TypeFamilies regression

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler | Version: 8.6.3 (Type checker) | 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: -------------------------------------+------------------------------------- The credit goes to wuzzeb for originally discovering this bug [https://www.reddit.com/r/haskell/comments/ad9a7k/strictdata_typefamilies_and... here]. I've minimized their test case slightly below: {{{#!hs {-# LANGUAGE StrictData #-} {-# LANGUAGE TypeFamilies #-} module Bug where data family T newtype instance T = MkT Int deriving Eq }}} With optimization enabled, this program compiles with GHC 8.0.2 through 8.4.4, but not with 8.6.3 or HEAD: {{{ $ /opt/ghc/8.4.4/bin/ghc -fforce-recomp -O Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) $ /opt/ghc/8.6.3/bin/ghc -fforce-recomp -O Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:6:39: error: • Couldn't match a lifted type with an unlifted type arising from the coercion of the method ‘==’ from type ‘GHC.Prim.Int# -> GHC.Prim.Int# -> Bool’ to type ‘T -> T -> Bool’ • When deriving the instance for (Eq T) | 6 | newtype instance T = MkT Int deriving Eq | ^^ }}} Based on the error message, it appears as if GHC mistakenly believes that the representation type of the `T` instance is `Int#`, rather than `Int`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Hm, this appears to be my fault, as this regression was introduced in commit eb680f2c0a365b12f9b867da6bb10e9ab4b328e0 (`Fix newtype instance GADTs`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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=,
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

#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] ,
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]

#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): The mention of `Int#` has me wondering: is GHC trying to unpack the `Int` field of `MkT`? If so, I would surely think that that's incorrect, since the idea of unpacking a newtype seems bogus, especially since GHC rejects this program: {{{ λ> newtype T = MkT {-# UNPACK #-} !Int <interactive>:1:13: error: • A newtype constructor cannot have a strictness annotation, but ‘MkT’ does • In the definition of data constructor ‘MkT’ In the newtype declaration for ‘T’ }}} Perhaps the implementation of `StrictData` misses this fact, however. I'll check the code to see if that is the case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by adamse): * cc: adamse (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): My hunch appears to be correct. The [https://gitlab.haskell.org/ghc/ghc/blob/master/compiler/basicTypes/MkId.hs#L... dataConSrcToImplBang] function is what is responsible for making decisions about strictness/unpacking w.r.t. `StrictData`: {{{#!hs -- | Unpack/Strictness decisions from source module dataConSrcToImplBang :: DynFlags -> FamInstEnvs -> Type -> HsSrcBang -> HsImplBang dataConSrcToImplBang dflags fam_envs arg_ty (HsSrcBang ann unpk NoSrcStrict) | xopt LangExt.StrictData dflags -- StrictData => strict field = dataConSrcToImplBang dflags fam_envs arg_ty (HsSrcBang ann unpk SrcStrict) | otherwise -- no StrictData => lazy field = HsLazy }}} Notice that this does not take into account whether the `Type` of the field belongs to a newtype or not, so this will indeed unpack the field of a newtype with `StrictData` + `-O` enabled. Yikes. One could fix this by propagating information about whether we're in a newtype or not to `dataConSrcToImplBang`. But then again, should we really even need to call `dataConSrcToImplBang` if we're dealing with a newtype? `dataConSrcToImplBang` is internal to `MkId` and only has one call site, so I'm inclined to just avoid invoking it at its call site, like so: {{{#!diff diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 5a6f1fbf96..fa3d6785b7 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -637,11 +637,15 @@ mkDataConRep dflags fam_envs wrap_name mb_bangs data_con -- Because we are going to apply the eq_spec args manually in the -- wrapper - arg_ibangs = - case mb_bangs of - Nothing -> zipWith (dataConSrcToImplBang dflags fam_envs) - orig_arg_tys orig_bangs - Just bangs -> bangs + new_tycon = isNewTyCon tycon + arg_ibangs + | new_tycon + = nOfThem (length orig_arg_tys) HsLazy + | otherwise + = case mb_bangs of + Nothing -> zipWith (dataConSrcToImplBang dflags fam_envs) + orig_arg_tys orig_bangs + Just bangs -> bangs (rep_tys_w_strs, wrappers) = unzip (zipWith dataConArgRep all_arg_tys (ev_ibangs ++ arg_ibangs)) @@ -650,7 +654,7 @@ mkDataConRep dflags fam_envs wrap_name mb_bangs data_con (rep_tys, rep_strs) = unzip (concat rep_tys_w_strs) wrapper_reqd = - (not (isNewTyCon tycon) + (not new_tycon -- (Most) newtypes have only a worker, with the exception -- of some newtypes written with GADT syntax. See below. && (any isBanged (ev_ibangs ++ arg_ibangs) }}} This certainly fixes the two programs in this ticket, and it passes the rest of the testsuite. Does this sound like the right approach? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -------------------------------------+------------------------------------- Comment (by simonpj): Good catch. I think you have the right approach. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16141: StrictData and TypeFamilies regression
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: closed
Priority: highest | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.6.3
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | typecheck/should_compile/T16141
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* testcase: => typecheck/should_compile/T16141
* status: patch => closed
* resolution: => fixed
Comment:
Landed in
[https://gitlab.haskell.org/ghc/ghc/commit/076f5862a9e46eef762ba19fb7b14e75fa...
076f5862a9e46eef762ba19fb7b14e75fa03c2c0]:
{{{
commit 076f5862a9e46eef762ba19fb7b14e75fa03c2c0
Author: Ryan Scott

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.6.4 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T16141 Blocked By: | Blocking: Related Tickets: #16191 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => merge * related: => #16191 * milestone: 8.8.1 => 8.6.4 Comment: Given the severity of this bug, and that fact that there have been multiple bug reports about this (see #16191 for another one), I'll optimistically mark this as a candidate for merging into the upcoming 8.6.4 release. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16141: StrictData and TypeFamilies regression
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: merge
Priority: highest | Milestone: 8.6.4
Component: Compiler (Type | Version: 8.6.3
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | typecheck/should_compile/T16141
Blocked By: | Blocking:
Related Tickets: #16191 | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88
-------------------------------------+-------------------------------------
Comment (by Marge Bot

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.6.4 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T16141 Blocked By: | Blocking: Related Tickets: #16191 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged with ff47e60a9d017e5d749ff5e29e61d6f1a558d142. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16141: StrictData and TypeFamilies regression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T16141 Blocked By: | Blocking: Related Tickets: #16191 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/88 -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge * milestone: 8.6.4 => 8.8.1 Comment: Also needs merging for 8.8.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16141#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC