Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- newtype ST# :: forall (r :: RuntimeRep). Type -> TYPE r -> Type where
- ST# :: forall (r :: RuntimeRep) (s :: Type) (a :: TYPE r). {..} -> ST# s a
- newtype ShortText# :: TYPE ('BoxedRep 'Unlifted) where
- ShortText# :: ByteArray# -> ShortText#
- newtype Text# :: TYPE ('TupleRep ['BoxedRep 'Unlifted, 'Int32Rep, 'Int32Rep]) where
- Text# :: (# ByteArray#, Int32#, Int32# #) -> Text#
- newtype PrimArray# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('BoxedRep 'Unlifted) where
- PrimArray# :: forall (r :: RuntimeRep) (a :: TYPE r). ByteArray# -> PrimArray# a
- 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 Bool# :: TYPE 'WordRep where
- pattern True# :: Bool#
- pattern False# :: Bool#
Base
newtype Maybe# :: forall (r :: RuntimeRep). TYPE r -> TYPE ('SumRep '['TupleRep '[], r]) where Source #
Unboxed variant of Maybe
.
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
.
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.
Text
newtype ShortText# :: TYPE ('BoxedRep 'Unlifted) where Source #
Unlifted variant of ShortText
.
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.
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#
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#
.
MutablePrimArray# :: forall (r :: RuntimeRep) (s :: Type) (a :: TYPE r). MutableByteArray# s -> MutablePrimArray# s a |