[GHC] #15777: Ordering of code in file affects compilation
GHC
ghc-devs at haskell.org
Thu Oct 18 21:38:21 UTC 2018
#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
More information about the ghc-tickets
mailing list