
#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