{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedNewtypes #-}
module Data.Unlifted
(
Maybe# (..)
, Either# (..)
, ST# (..)
, ShortText# (..)
, Text# (..)
, PrimArray# (..)
, MutablePrimArray# (..)
, Bool# (..)
, pattern True#
, pattern False#
) where
import Data.Kind (Type)
import GHC.Exts (ByteArray#, Int32#, Levity (Unlifted), MutableByteArray#, RuntimeRep (..), State#, TYPE, Word#)
newtype ST# :: forall (r :: RuntimeRep). Type -> TYPE r -> Type where
ST# ::
forall (r :: RuntimeRep) (s :: Type) (a :: TYPE r).
{ forall s a. ST# s a -> State# s -> (# State# s, a #)
unST# :: State# s -> (# State# s, a #)
} ->
ST# s a
newtype Bool# :: TYPE 'WordRep where
Bool# :: Word# -> Bool#
newtype Maybe# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('SumRep '[ 'TupleRep '[], r]) where
Maybe# :: forall (r :: RuntimeRep) (a :: TYPE r). (# (# #) | a #) -> Maybe# @r a
newtype Either# :: forall (ra :: RuntimeRep) (rb :: RuntimeRep). TYPE ra -> TYPE rb -> TYPE ('SumRep '[ra, rb]) where
Either# :: forall (ra :: RuntimeRep) (rb :: RuntimeRep) (a :: TYPE ra) (b :: TYPE rb). (# a | b #) -> Either# a b
{-# COMPLETE True#, False# #-}
pattern True# :: Bool#
pattern $mTrue# :: forall {r}. Bool# -> ((# #) -> r) -> ((# #) -> r) -> r
$bTrue# :: (# #) -> Bool#
True# = Bool# 1##
pattern False# :: Bool#
pattern $mFalse# :: forall {r}. Bool# -> ((# #) -> r) -> ((# #) -> r) -> r
$bFalse# :: (# #) -> Bool#
False# = Bool# 0##
newtype MutablePrimArray# :: forall (r :: RuntimeRep). Type -> TYPE r -> TYPE ('BoxedRep 'Unlifted) where
MutablePrimArray# :: forall (r :: RuntimeRep) (s :: Type) (a :: TYPE r). MutableByteArray# s -> MutablePrimArray# s a
newtype PrimArray# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('BoxedRep 'Unlifted) where
PrimArray# :: forall (r :: RuntimeRep) (a :: TYPE r). ByteArray# -> PrimArray# a
newtype ShortText# :: TYPE ('BoxedRep 'Unlifted) where
ShortText# :: ByteArray# -> ShortText#
newtype Text# :: TYPE ('TupleRep ['BoxedRep 'Unlifted, 'Int32Rep, 'Int32Rep]) where
Text# :: (# ByteArray#, Int32#, Int32# #) -> Text#