foundation-0.0.7: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Primitive

Contents

Description

Different collections (list, vector, string, ..) unified under 1 API. an API to rules them all, and in the darkness bind them.

Synopsis

Documentation

class Eq ty => PrimType ty where Source #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Methods

primSizeInBytes :: Proxy ty -> Size8 Source #

get the size in bytes of a ty element

primBaUIndex :: ByteArray# -> Offset ty -> ty Source #

return the element stored at a specific index

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty Source #

Read an element at an index in a mutable array

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () Source #

Write an element to a specific cell in a mutable array.

primAddrIndex :: Addr# -> Offset ty -> ty Source #

Read from Address, without a state. the value read should be considered a constant for all pratical purpose, otherwise bad thing will happens.

primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty Source #

Read a value from Addr in a specific primitive monad

primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () Source #

Write a value to Addr in a specific primitive monad

Instances

PrimType Char Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 
PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

class (Functor m, Applicative m, Monad m) => PrimMonad m where Source #

Primitive monad that can handle mutation.

For example: IO and ST.

Associated Types

type PrimState m Source #

type of state token associated with the PrimMonad m

type PrimVar m :: * -> * Source #

type of variable associated with the PrimMonad m

Methods

primitive :: (State# (PrimState m) -> (#State# (PrimState m), a#)) -> m a Source #

Unwrap the State# token to pass to a function a primitive function that returns an unboxed state and a value.

primThrow :: Exception e => e -> m a Source #

Throw Exception in the primitive monad

unPrimMonad :: m a -> State# (PrimState m) -> (#State# (PrimState m), a#) Source #

Run a Prim monad from a dedicated state#

primVarNew :: a -> m (PrimVar m a) Source #

Build a new variable in the Prim Monad

primVarRead :: PrimVar m a -> m a Source #

Read the variable in the Prim Monad

primVarWrite :: PrimVar m a -> a -> m () Source #

Write the variable in the Prim Monad

Instances

PrimMonad IO Source # 

Associated Types

type PrimState (IO :: * -> *) :: * Source #

type PrimVar (IO :: * -> *) :: * -> * Source #

PrimMonad (ST s) Source # 

Associated Types

type PrimState (ST s :: * -> *) :: * Source #

type PrimVar (ST s :: * -> *) :: * -> * Source #

Methods

primitive :: (State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#)) -> ST s a Source #

primThrow :: Exception e => e -> ST s a Source #

unPrimMonad :: ST s a -> State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#) Source #

primVarNew :: a -> ST s (PrimVar (ST s) a) Source #

primVarRead :: PrimVar (ST s) a -> ST s a Source #

primVarWrite :: PrimVar (ST s) a -> a -> ST s () Source #

endianess

class ByteSwap a Source #

Class of types that can be byte-swapped.

e.g. Word16, Word32, Word64

Minimal complete definition

byteSwap

newtype LE a Source #

Little Endian value

Constructors

LE 

Fields

Instances

Eq a => Eq (LE a) Source # 

Methods

(==) :: LE a -> LE a -> Bool #

(/=) :: LE a -> LE a -> Bool #

(ByteSwap a, Ord a) => Ord (LE a) Source # 

Methods

compare :: LE a -> LE a -> Ordering #

(<) :: LE a -> LE a -> Bool #

(<=) :: LE a -> LE a -> Bool #

(>) :: LE a -> LE a -> Bool #

(>=) :: LE a -> LE a -> Bool #

max :: LE a -> LE a -> LE a #

min :: LE a -> LE a -> LE a #

Show a => Show (LE a) Source # 

Methods

showsPrec :: Int -> LE a -> ShowS #

show :: LE a -> String #

showList :: [LE a] -> ShowS #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

StorableFixed (LE Word16) Source # 

Methods

size :: proxy (LE Word16) -> Size Word8 Source #

alignment :: proxy (LE Word16) -> Size Word8 Source #

StorableFixed (LE Word32) Source # 

Methods

size :: proxy (LE Word32) -> Size Word8 Source #

alignment :: proxy (LE Word32) -> Size Word8 Source #

StorableFixed (LE Word64) Source # 

Methods

size :: proxy (LE Word64) -> Size Word8 Source #

alignment :: proxy (LE Word64) -> Size Word8 Source #

Storable (LE Word16) Source # 

Methods

peek :: Ptr (LE Word16) -> IO (LE Word16) Source #

poke :: Ptr (LE Word16) -> LE Word16 -> IO () Source #

Storable (LE Word32) Source # 

Methods

peek :: Ptr (LE Word32) -> IO (LE Word32) Source #

poke :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

Storable (LE Word64) Source # 

Methods

peek :: Ptr (LE Word64) -> IO (LE Word64) Source #

poke :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

toLE :: ByteSwap a => a -> LE a Source #

Convert a value in cpu endianess to little endian

fromLE :: ByteSwap a => LE a -> a Source #

Convert from a little endian value to the cpu endianness

newtype BE a Source #

Big Endian value

Constructors

BE 

Fields

Instances

Eq a => Eq (BE a) Source # 

Methods

(==) :: BE a -> BE a -> Bool #

(/=) :: BE a -> BE a -> Bool #

(ByteSwap a, Ord a) => Ord (BE a) Source # 

Methods

compare :: BE a -> BE a -> Ordering #

(<) :: BE a -> BE a -> Bool #

(<=) :: BE a -> BE a -> Bool #

(>) :: BE a -> BE a -> Bool #

(>=) :: BE a -> BE a -> Bool #

max :: BE a -> BE a -> BE a #

min :: BE a -> BE a -> BE a #

Show a => Show (BE a) Source # 

Methods

showsPrec :: Int -> BE a -> ShowS #

show :: BE a -> String #

showList :: [BE a] -> ShowS #

PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

StorableFixed (BE Word16) Source # 

Methods

size :: proxy (BE Word16) -> Size Word8 Source #

alignment :: proxy (BE Word16) -> Size Word8 Source #

StorableFixed (BE Word32) Source # 

Methods

size :: proxy (BE Word32) -> Size Word8 Source #

alignment :: proxy (BE Word32) -> Size Word8 Source #

StorableFixed (BE Word64) Source # 

Methods

size :: proxy (BE Word64) -> Size Word8 Source #

alignment :: proxy (BE Word64) -> Size Word8 Source #

Storable (BE Word16) Source # 

Methods

peek :: Ptr (BE Word16) -> IO (BE Word16) Source #

poke :: Ptr (BE Word16) -> BE Word16 -> IO () Source #

Storable (BE Word32) Source # 

Methods

peek :: Ptr (BE Word32) -> IO (BE Word32) Source #

poke :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

Storable (BE Word64) Source # 

Methods

peek :: Ptr (BE Word64) -> IO (BE Word64) Source #

poke :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

toBE :: ByteSwap a => a -> BE a Source #

Convert a value in cpu endianess to big endian

fromBE :: ByteSwap a => BE a -> a Source #

Convert from a big endian value to the cpu endianness

Integral convertion

class IntegralUpsize a b where Source #

Upsize an integral value

The destination type b size need to be greater or equal than the size type of a

Minimal complete definition

integralUpsize

Methods

integralUpsize :: a -> b Source #

Instances

IntegralUpsize Int Int64 Source # 
IntegralUpsize Int Integer Source # 
IntegralUpsize Int8 Int Source # 
IntegralUpsize Int8 Int16 Source # 
IntegralUpsize Int8 Int32 Source # 
IntegralUpsize Int8 Int64 Source # 
IntegralUpsize Int8 Integer Source # 
IntegralUpsize Int16 Int Source # 
IntegralUpsize Int16 Int32 Source # 
IntegralUpsize Int16 Int64 Source # 
IntegralUpsize Int16 Integer Source # 
IntegralUpsize Int32 Int Source # 
IntegralUpsize Int32 Int64 Source # 
IntegralUpsize Int32 Integer Source # 
IntegralUpsize Int64 Integer Source # 
IntegralUpsize Word Integer Source # 
IntegralUpsize Word Word64 Source # 
IntegralUpsize Word Natural Source # 
IntegralUpsize Word8 Int Source # 
IntegralUpsize Word8 Int16 Source # 
IntegralUpsize Word8 Int32 Source # 
IntegralUpsize Word8 Int64 Source # 
IntegralUpsize Word8 Integer Source # 
IntegralUpsize Word8 Word Source # 
IntegralUpsize Word8 Word16 Source # 
IntegralUpsize Word8 Word32 Source # 
IntegralUpsize Word8 Word64 Source # 
IntegralUpsize Word8 Natural Source # 
IntegralUpsize Word16 Integer Source # 
IntegralUpsize Word16 Word Source # 
IntegralUpsize Word16 Word32 Source # 
IntegralUpsize Word16 Word64 Source # 
IntegralUpsize Word16 Natural Source # 
IntegralUpsize Word32 Integer Source # 
IntegralUpsize Word32 Word Source # 
IntegralUpsize Word32 Word64 Source # 
IntegralUpsize Word32 Natural Source # 
IntegralUpsize Word64 Integer Source # 
IntegralUpsize Word64 Natural Source # 
IntegralUpsize Natural Integer Source # 

class IntegralDownsize a b where Source #

Downsize an integral value

Minimal complete definition

integralDownsizeCheck

Methods

integralDownsize :: a -> b Source #

integralDownsize :: a ~ b => a -> b Source #

integralDownsizeCheck :: a -> Maybe b Source #

Instances

IntegralDownsize Int Int8 Source # 
IntegralDownsize Int Int16 Source # 
IntegralDownsize Int Int32 Source # 
IntegralDownsize Integer Int8 Source # 
IntegralDownsize Integer Int16 Source # 
IntegralDownsize Integer Int32 Source # 
IntegralDownsize Integer Int64 Source # 
IntegralDownsize Integer Word8 Source # 
IntegralDownsize Integer Word16 Source # 
IntegralDownsize Integer Word32 Source # 
IntegralDownsize Integer Word64 Source # 
IntegralDownsize Integer Natural Source # 
IntegralDownsize Word16 Word8 Source # 
IntegralDownsize Word32 Word8 Source # 
IntegralDownsize Word32 Word16 Source # 
IntegralDownsize Word64 Word8 Source # 
IntegralDownsize Word64 Word16 Source # 
IntegralDownsize Word64 Word32 Source # 
IntegralDownsize Natural Word8 Source # 
IntegralDownsize Natural Word16 Source # 
IntegralDownsize Natural Word32 Source # 
IntegralDownsize Natural Word64 Source # 

class IntegralCast a b where Source #

Cast an integral value to another value that have the same representional size

Methods

integralCast :: a -> b Source #

integralCast :: a ~ b => a -> b Source #