[GHC] #15318: Core Lint error involving newtype family instances with wrappers

#15318: Core Lint error involving newtype family instances with wrappers
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
(Type checker) |
Keywords: TypeFamilies | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following program gives a Core Lint error on GHC 8.4 and later:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where
data family Sn a
newtype instance Sn (Either a b) where
SnC :: forall b a. Char -> Sn (Either a b)
}}}
{{{
$ /opt/ghc/8.4.3/bin/ghc -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 body of lambda with binder dt_aZm :: Char]
From-type of Cast differs from type of enclosed expression
From-type: R:SnEither a_auS b_auR
Type of enclosed expr: Sn (Either a_auS b_auR)
Actual enclosed expr: dt_aZm
`cast` (Sym (N:R:SnEither[0]

#15318: Core Lint error involving newtype family instances with wrappers -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.3 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * differential: => Phab:D4902 Comment: See https://phabricator.haskell.org/D4902 Which is Richard's fix cherry-picked. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15318#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15318: Core Lint error involving newtype family instances with wrappers -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.3 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4902 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, Phab:D4902 will fix the bug, but it perpetuates a mistake! Consider {{{ data family S a data family T a data instance S [a] = MkS a newtype instance T [a] = MkT a }}} Currently, we get this: {{{ data SList a = MkS a axiom coS a :: SList a ~ S [a] -- Wrapper for MkS $WMkS :: a -> S [a] $WMkS x = MkS x |> coS a -- newtype TList a = MkT a axiom coTList a :: a ~ TList a axiom coT a :: TList a ~ T [a] -- Worker for MkT MkT :: a -> T [a] MkT x = x |> coTList a |> coT a }}} Notice the inconsistency: the cast that takes us from the representation type to the final user type is done in the ''wrapper'' for data types, but in the ''worker'' for a newtype. (Reminder: for data types the worker isn't an executable function, it's the Core data constructor; but for a newtype the "worker" is an executable function that expands to a cast.) This inconsistency shows up in the `MkId` functions `wrapNewTypeBody` and `unwrapNewTypeBody`. The former wraps two casts (as above) while the latter unwraps only one! I think we can readily remove the inconsistency: * Don't export `wrapNewTypeBody` from `MkId`; it is not used outside. * Remove the extra cast from `wrapNewTypeBody` * Do not make the change to `mkDataConRep` proposed in Phab:D4902. * Make a wrapper for family-instance newtypes. Do this by making `wwrapper_reqd` return `True` for ''all'' types for which `isFamInstTyCon` holds. (Currently that predicate is not tested for newtypes.) I think that might be it. It solves the problem at source, produces less code and less to explain (because it's consistent). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15318#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15318: Core Lint error involving newtype family instances with wrappers
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.4.3
checker) |
Resolution: | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4902
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15318: Core Lint error involving newtype family instances with wrappers -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.3 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: indexed- crash or panic | types/should_compile/T15318 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => merge * testcase: => indexed-types/should_compile/T15318 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15318#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15318: Core Lint error involving newtype family instances with wrappers -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.3 checker) | Resolution: fixed | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: indexed- crash or panic | types/should_compile/T15318 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4902 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with eb680f2c0a365b12f9b867da6bb10e9ab4b328e0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15318#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC