[GHC] #15777: Ordering of code in file affects compilation

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 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: -------------------------------------+------------------------------------- consider the following module: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} -- | Conversion between unlifted and lifted datatypes module Packed.Levity ( -- * Types Rep , Levity(..) ) where import Data.Kind (Type) import GHC.Types (TYPE, RuntimeRep(..), Int(..), Word(..)) import GHC.Exts (Int#, Word#, ByteArray#) type family Rep (a :: Type) :: RuntimeRep type instance Rep Int = IntRep type instance Rep Word = WordRep type Stuff# = (# Int#, Int# #) data Stuff = Stuff Int# Int# type instance Rep Stuff = TupleRep '[ 'IntRep, 'IntRep ] stuff# :: (# Int#, Int# #) -> Stuff stuff# (# x, y #) = Stuff x y unStuff# :: Stuff -> (# Int#, Int# #) unStuff# (Stuff x y) = (# x, y #) class Levity (a :: Type) where type Unlifted a :: TYPE (Rep a) box :: Unlifted a -> a unbox :: a -> Unlifted a instance Levity Int where type Unlifted Int = Int# box = I# unbox (I# i) = i instance Levity Word where type Unlifted Word = Word# box = W# unbox (W# w) = w instance Levity Stuff where type Unlifted Stuff = Stuff# box = stuff# unbox = unStuff# }}} This succeeds to compile. Now, if we move everything from `type family Rep` to `unStuff# (` to the bottom of the module, it fails to compile. {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} -- | Conversion between unlifted and lifted datatypes module Packed.Levity ( -- * Types Rep , Levity(..) ) where import Data.Kind (Type) import GHC.Types (TYPE, RuntimeRep(..), Int(..), Word(..)) import GHC.Exts (Int#, Word#, ByteArray#) class Levity (a :: Type) where type Unlifted a :: TYPE (Rep a) box :: Unlifted a -> a unbox :: a -> Unlifted a instance Levity Int where type Unlifted Int = Int# box = I# unbox (I# i) = i instance Levity Word where type Unlifted Word = Word# box = W# unbox (W# w) = w instance Levity Stuff where type Unlifted Stuff = Stuff# box = stuff# unbox = unStuff# type family Rep (a :: Type) :: RuntimeRep type instance Rep Int = IntRep type instance Rep Word = WordRep type Stuff# = (# Int#, Int# #) data Stuff = Stuff Int# Int# type instance Rep Stuff = TupleRep '[ 'IntRep, 'IntRep ] stuff# :: (# Int#, Int# #) -> Stuff stuff# (# x, y #) = Stuff x y unStuff# :: Stuff -> (# Int#, Int# #) unStuff# (Stuff x y) = (# x, y #) }}} {{{ ts.hs:33:25-30: error: • Expected kind ‘TYPE (Rep Stuff)’, but ‘Stuff#’ has kind ‘TYPE ('TupleRep '['IntRep, 'IntRep])’ • In the type ‘Stuff#’ In the type instance declaration for ‘Unlifted’ In the instance declaration for ‘Levity Stuff’ | 33 | type Unlifted Stuff = Stuff# | ^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12088 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #12088 Comment: Thanks for the bug report. This is a duplicate of #12088 (as well as many other tickets listed in its related tickets pane), so I'll close this ticket in favor of #12088. As a crude workaround, you can use Template Haskell to force GHC to see the light. That is, this slight variant of the second program typechecks: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} -- | Conversion between unlifted and lifted datatypes module Packed.Levity ( -- * Types Rep , Levity(..) ) where import Data.Kind (Type) import GHC.Types (TYPE, RuntimeRep(..), Int(..), Word(..)) import GHC.Exts (Int#, Word#, ByteArray#) class Levity (a :: Type) where type Unlifted a :: TYPE (Rep a) box :: Unlifted a -> a unbox :: a -> Unlifted a instance Levity Int where type Unlifted Int = Int# box = I# unbox (I# i) = i instance Levity Word where type Unlifted Word = Word# box = W# unbox (W# w) = w type family Rep (a :: Type) :: RuntimeRep type instance Rep Int = IntRep type instance Rep Word = WordRep type Stuff# = (# Int#, Int# #) data Stuff = Stuff Int# Int# type instance Rep Stuff = TupleRep '[ 'IntRep, 'IntRep ] $(pure []) instance Levity Stuff where type Unlifted Stuff = Stuff# box = stuff# unbox = unStuff# stuff# :: (# Int#, Int# #) -> Stuff stuff# (# x, y #) = Stuff x y unStuff# :: Stuff -> (# Int#, Int# #) unStuff# (Stuff x y) = (# x, y #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12088 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by chessai): Thanks for the quick response. Curious - why does that hack work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12088 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): When kind-checking, GHC performs strongly-connected component (SCC) analysis to determine which declarations depend on the presence of other declarations. In your example, the `type Unlifted Stuff = Stuff#` instance declaration depends on the `type instance Rep Stuff = TupleRep '[ 'IntRep, 'IntRep ]` instance declaration in order to kind-check, so a proper SCC analysis should put the former declaration //after// the latter one. Because of #12088, however, this does not happen correctly, and these declarations get processed out of dependency order. The use of a Template Haskell splice (such as `$(pure [])`) is a gruesome hack which forces the declarations following the splice to be processed //after// the declarations preceding the splice. This is often an annoying weakness of Template Haskell, but in this particular case, it happens to work to our advantage :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12088 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by chessai): Ah, ok. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15777: Ordering of code in file affects compilation -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12088 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): One other trick worth noting (that I learned recently from #15561) is that open and closed type families behave differently in SCC analysis, so turning `Rep` into a closed type family actually makes this typecheck. That is to say, the following compiles: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} -- | Conversion between unlifted and lifted datatypes module Packed.Levity ( -- * Types Rep , Levity(..) ) where import Data.Kind (Type) import GHC.Types (TYPE, RuntimeRep(..), Int(..), Word(..)) import GHC.Exts (Int#, Word#, ByteArray#) class Levity (a :: Type) where type Unlifted a :: TYPE (Rep a) box :: Unlifted a -> a unbox :: a -> Unlifted a instance Levity Int where type Unlifted Int = Int# box = I# unbox (I# i) = i instance Levity Word where type Unlifted Word = Word# box = W# unbox (W# w) = w instance Levity Stuff where type Unlifted Stuff = Stuff# box = stuff# unbox = unStuff# type family Rep (a :: Type) :: RuntimeRep where Rep Int = IntRep Rep Word = WordRep Rep Stuff = TupleRep '[ 'IntRep, 'IntRep ] type Stuff# = (# Int#, Int# #) data Stuff = Stuff Int# Int# stuff# :: (# Int#, Int# #) -> Stuff stuff# (# x, y #) = Stuff x y unStuff# :: Stuff -> (# Int#, Int# #) unStuff# (Stuff x y) = (# x, y #) }}} You may not be able to get away with making `Rep` a closed type family in the actual program that you're writing, but I thought I'd point it out nonetheless, since I was myself unaware of this fact until today. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15777#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC