[GHC] #13955: Backpack does not handle unlifted types
GHC
ghc-devs at haskell.org
Mon Jul 10 17:58:26 UTC 2017
#13955: Backpack does not handle unlifted types
-------------------------------------+-------------------------------------
Reporter: andrewthad | Owner: (none)
Type: feature | Status: new
request |
Priority: low | Milestone:
Component: Compiler | Version: 8.2.1-rc2
Keywords: backpack | Operating System: Unknown/Multiple
LevityPolymorphism |
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
In the code snippet below, I attempt to use backpack with levity
polymorphism:
{{{
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
unit number-unknown where
signature NumberUnknown where
import GHC.Types
data Number
plus :: Number -> Number -> Number
multiply :: Number -> Number -> Number
module NumberStuff where
import NumberUnknown
funcA :: Number -> Number -> Number
funcA x y = plus x (multiply x y)
unit number-int where
module NumberUnknown where
type Number = Int
plus :: Int -> Int -> Int
plus = (+)
multiply :: Int -> Int -> Int
multiply = (*)
unit number-unboxed-int where
module NumberUnknown where
import GHC.Prim
type Number = Int#
plus :: Int# -> Int# -> Int#
plus = (+#)
multiply :: Int# -> Int# -> Int#
multiply = (*#)
unit main where
dependency number-unknown[NumberUnknown=number-unboxed-
int:NumberUnknown]
module Main where
import NumberStuff
main = putStrLn "Hello world!"
}}}
Compiling this with `ghc --backpack packer.bkp` fails with the following
error:
{{{
- Type constructor ‘Number’ has conflicting definitions in the module
and its hsig file
Main module: type Number = GHC.Prim.Int# :: TYPE 'GHC.Types.IntRep
Hsig file: data Number
The types have different kinds
- while checking that number-unboxed-int:NumberUnknown implements
signature NumberUnknown in number-unknown[NumberUnknown=number-unboxed-
int:NumberUnknown]
type Number = Int#
}}}
The error is pretty clear: `Number` can only be instantiated by types of
kind `Type` (aka `TYPE LiftedRep`). Even while remaining levity
monomorphic, there doesn't seem to be a way to pick a different kind. For
example, redefining `Number` in the signature as
{{{
data Number :: TYPE IntRep
}}}
leads to the following immediate failure:
{{{
Kind signature on data type declaration has non-* return kind TYPE 'IntRep
}}}
I do not understand any of the internals of backpack, so I do not
understand if there's anything fundamental that makes this impossible.
Going one step further, I would like to be able to do something like this
(the syntax here is not even currently valid for a backpack signature):
{{{
type MyRep :: RuntimeRep
data Number :: TYPE MyRep
}}}
This may be instantiated with something like this:
{{{
type MyRep = IntRep
type Number = Int#
}}}
And then end users would be able to monomorphize levity-polymorphic
functions. This would be really neat because there is currently no way to
do this in GHC.
So, I guess there are really two feature requests in here. One is the
ability to use unlifted data types with backpack. The other is the ability
to use backpack to monomorphize levity-polymorphic functions.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13955>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list