unlifted-0.2.2.0: Unlifted and levity-polymorphic types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Unlifted

Synopsis

Base

newtype Maybe# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('SumRep '['TupleRep '[], r]) where Source #

Unboxed variant of Maybe.

Constructors

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 Source #

Unboxed variant of Either.

Constructors

Either# :: forall (ra :: RuntimeRep) (rb :: RuntimeRep) (a :: TYPE ra) (b :: TYPE rb). (# a | b #) -> Either# a b 

newtype ST# :: forall (r :: RuntimeRep). Type -> TYPE r -> Type where Source #

Variant of ST where the argument type does not have to be lifted. This does not have a monad instance and is difficult to use.

Constructors

ST# 

Fields

Text

newtype ShortText# :: TYPE ('BoxedRep 'Unlifted) where Source #

Unlifted variant of ShortText.

Constructors

ShortText# :: ByteArray# -> ShortText# 

newtype Text# :: TYPE ('TupleRep ['BoxedRep 'Unlifted, 'Int32Rep, 'Int32Rep]) where Source #

Unboxed variant of Text. This includes a somewhat dubious restriction that on the offset and length that prevents byte arrays larger than 2GiB from being used as the backing store.

This decision makes the type work well in the vext library, and it makes the in-memory format close to what Apache Arrow uses.

Constructors

Text# :: (# ByteArray#, Int32#, Int32# #) -> Text# 

Arrays

newtype PrimArray# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('BoxedRep 'Unlifted) where Source #

This resembles the PrimArray type from primitive, but the phantom parameter is an unboxed type, not a lifted type. For example:

  • PrimArray Word8
  • PrimArray# Word8#

Constructors

PrimArray# :: forall (r :: RuntimeRep) (a :: TYPE r). ByteArray# -> PrimArray# a 

newtype MutablePrimArray# :: forall (r :: RuntimeRep). Type -> TYPE r -> TYPE ('BoxedRep 'Unlifted) where Source #

Mutable variant of PrimArray#.

Constructors

MutablePrimArray# :: forall (r :: RuntimeRep) (s :: Type) (a :: TYPE r). MutableByteArray# s -> MutablePrimArray# s a 

Boolean

newtype Bool# :: TYPE 'WordRep where Source #

Unboxed variant of Bool.

Constructors

Bool# :: Word# -> Bool# 

pattern True# :: Bool# Source #

pattern False# :: Bool# Source #