Skip to content

Instantly share code, notes, and snippets.

@chessai
Created October 18, 2018 21:24
Show Gist options
  • Save chessai/64c4f08dde865371d9a536d43c3917e5 to your computer and use it in GitHub Desktop.
Save chessai/64c4f08dde865371d9a536d43c3917e5 to your computer and use it in GitHub Desktop.
{-# 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#
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment