foundation-0.0.15: Alternative prelude with batteries and no dependencies

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

Foundation.Primitive

Contents

Description

 

Synopsis

Documentation

class Eq ty => PrimType ty where #

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 -> CountOf Word8 #

get the size in bytes of a ty element

primShiftToBytes :: Proxy * ty -> Int #

get the shift size

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

return the element stored at a specific index

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

Read an element at an index in a mutable array

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

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

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

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 #

Read a value from Addr in a specific primitive monad

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

Write a value to Addr in a specific primitive monad

Instances

PrimType Char 
PrimType Double 
PrimType Float 
PrimType Int 
PrimType Int8 
PrimType Int16 
PrimType Int32 
PrimType Int64 
PrimType Word 
PrimType Word8 
PrimType Word16 
PrimType Word32 
PrimType Word64 
PrimType CChar 
PrimType CUChar 
PrimType Word256 
PrimType Word128 
PrimType Char7 
PrimType Seconds # 
PrimType NanoSeconds # 
PrimType a => PrimType (LE a) 

Methods

primSizeInBytes :: Proxy * (LE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (LE a) -> Int #

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

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

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

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

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

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

PrimType a => PrimType (BE a) 

Methods

primSizeInBytes :: Proxy * (BE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (BE a) -> Int #

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

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

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

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

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

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

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

Primitive monad that can handle mutation.

For example: IO and ST.

Associated Types

type PrimState (m :: * -> *) :: * #

type of state token associated with the PrimMonad m

type PrimVar (m :: * -> *) :: * -> * #

type of variable associated with the PrimMonad m

Methods

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

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 #

Throw Exception in the primitive monad

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

Run a Prim monad from a dedicated state#

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

Build a new variable in the Prim Monad

primVarRead :: PrimVar m a -> m a #

Read the variable in the Prim Monad

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

Write the variable in the Prim Monad

Instances

PrimMonad IO 

Associated Types

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

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

PrimMonad (ST s) 

Associated Types

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

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

Methods

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

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

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

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

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

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

endianess

class ByteSwap a #

Class of types that can be byte-swapped.

e.g. Word16, Word32, Word64

Minimal complete definition

byteSwap

newtype LE a :: * -> * #

Little Endian value

Constructors

LE 

Fields

Instances

Eq a => Eq (LE a) 

Methods

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

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

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

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) 

Methods

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

show :: LE a -> String #

showList :: [LE a] -> ShowS #

Bits a => Bits (LE a) 

Methods

(.&.) :: LE a -> LE a -> LE a #

(.|.) :: LE a -> LE a -> LE a #

xor :: LE a -> LE a -> LE a #

complement :: LE a -> LE a #

shift :: LE a -> Int -> LE a #

rotate :: LE a -> Int -> LE a #

zeroBits :: LE a #

bit :: Int -> LE a #

setBit :: LE a -> Int -> LE a #

clearBit :: LE a -> Int -> LE a #

complementBit :: LE a -> Int -> LE a #

testBit :: LE a -> Int -> Bool #

bitSizeMaybe :: LE a -> Maybe Int #

bitSize :: LE a -> Int #

isSigned :: LE a -> Bool #

shiftL :: LE a -> Int -> LE a #

unsafeShiftL :: LE a -> Int -> LE a #

shiftR :: LE a -> Int -> LE a #

unsafeShiftR :: LE a -> Int -> LE a #

rotateL :: LE a -> Int -> LE a #

rotateR :: LE a -> Int -> LE a #

popCount :: LE a -> Int #

PrimType a => PrimType (LE a) 

Methods

primSizeInBytes :: Proxy * (LE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (LE a) -> Int #

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

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

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

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

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

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

PrimMemoryComparable a => PrimMemoryComparable (LE a) 
NormalForm a => NormalForm (LE a) 

Methods

toNormalForm :: LE a -> () #

StorableFixed (LE Word16) # 

Methods

size :: proxy (LE Word16) -> CountOf Word8 #

alignment :: proxy (LE Word16) -> CountOf Word8 #

StorableFixed (LE Word32) # 

Methods

size :: proxy (LE Word32) -> CountOf Word8 #

alignment :: proxy (LE Word32) -> CountOf Word8 #

StorableFixed (LE Word64) # 

Methods

size :: proxy (LE Word64) -> CountOf Word8 #

alignment :: proxy (LE Word64) -> CountOf Word8 #

StorableFixed (LE Word256) # 

Methods

size :: proxy (LE Word256) -> CountOf Word8 #

alignment :: proxy (LE Word256) -> CountOf Word8 #

StorableFixed (LE Word128) # 

Methods

size :: proxy (LE Word128) -> CountOf Word8 #

alignment :: proxy (LE Word128) -> CountOf Word8 #

Storable (LE Word16) # 

Methods

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

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

Storable (LE Word32) # 

Methods

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

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

Storable (LE Word64) # 

Methods

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

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

Storable (LE Word256) # 

Methods

peek :: Ptr (LE Word256) -> IO (LE Word256) #

poke :: Ptr (LE Word256) -> LE Word256 -> IO () #

Storable (LE Word128) # 

Methods

peek :: Ptr (LE Word128) -> IO (LE Word128) #

poke :: Ptr (LE Word128) -> LE Word128 -> IO () #

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

Convert a value in cpu endianess to little endian

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

Convert from a little endian value to the cpu endianness

newtype BE a :: * -> * #

Big Endian value

Constructors

BE 

Fields

Instances

Eq a => Eq (BE a) 

Methods

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

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

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

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) 

Methods

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

show :: BE a -> String #

showList :: [BE a] -> ShowS #

Bits a => Bits (BE a) 

Methods

(.&.) :: BE a -> BE a -> BE a #

(.|.) :: BE a -> BE a -> BE a #

xor :: BE a -> BE a -> BE a #

complement :: BE a -> BE a #

shift :: BE a -> Int -> BE a #

rotate :: BE a -> Int -> BE a #

zeroBits :: BE a #

bit :: Int -> BE a #

setBit :: BE a -> Int -> BE a #

clearBit :: BE a -> Int -> BE a #

complementBit :: BE a -> Int -> BE a #

testBit :: BE a -> Int -> Bool #

bitSizeMaybe :: BE a -> Maybe Int #

bitSize :: BE a -> Int #

isSigned :: BE a -> Bool #

shiftL :: BE a -> Int -> BE a #

unsafeShiftL :: BE a -> Int -> BE a #

shiftR :: BE a -> Int -> BE a #

unsafeShiftR :: BE a -> Int -> BE a #

rotateL :: BE a -> Int -> BE a #

rotateR :: BE a -> Int -> BE a #

popCount :: BE a -> Int #

PrimType a => PrimType (BE a) 

Methods

primSizeInBytes :: Proxy * (BE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (BE a) -> Int #

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

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

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

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

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

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

PrimMemoryComparable a => PrimMemoryComparable (BE a) 
NormalForm a => NormalForm (BE a) 

Methods

toNormalForm :: BE a -> () #

StorableFixed (BE Word16) # 

Methods

size :: proxy (BE Word16) -> CountOf Word8 #

alignment :: proxy (BE Word16) -> CountOf Word8 #

StorableFixed (BE Word32) # 

Methods

size :: proxy (BE Word32) -> CountOf Word8 #

alignment :: proxy (BE Word32) -> CountOf Word8 #

StorableFixed (BE Word64) # 

Methods

size :: proxy (BE Word64) -> CountOf Word8 #

alignment :: proxy (BE Word64) -> CountOf Word8 #

StorableFixed (BE Word256) # 

Methods

size :: proxy (BE Word256) -> CountOf Word8 #

alignment :: proxy (BE Word256) -> CountOf Word8 #

StorableFixed (BE Word128) # 

Methods

size :: proxy (BE Word128) -> CountOf Word8 #

alignment :: proxy (BE Word128) -> CountOf Word8 #

Storable (BE Word16) # 

Methods

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

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

Storable (BE Word32) # 

Methods

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

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

Storable (BE Word64) # 

Methods

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

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

Storable (BE Word256) # 

Methods

peek :: Ptr (BE Word256) -> IO (BE Word256) #

poke :: Ptr (BE Word256) -> BE Word256 -> IO () #

Storable (BE Word128) # 

Methods

peek :: Ptr (BE Word128) -> IO (BE Word128) #

poke :: Ptr (BE Word128) -> BE Word128 -> IO () #

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

Convert a value in cpu endianess to big endian

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

Convert from a big endian value to the cpu endianness

Integral convertion

class IntegralUpsize a b where #

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 #

Instances

IntegralUpsize Int Int64 

Methods

integralUpsize :: Int -> Int64 #

IntegralUpsize Int8 Int 

Methods

integralUpsize :: Int8 -> Int #

IntegralUpsize Int8 Int16 

Methods

integralUpsize :: Int8 -> Int16 #

IntegralUpsize Int8 Int32 

Methods

integralUpsize :: Int8 -> Int32 #

IntegralUpsize Int8 Int64 

Methods

integralUpsize :: Int8 -> Int64 #

IntegralUpsize Int16 Int 

Methods

integralUpsize :: Int16 -> Int #

IntegralUpsize Int16 Int32 
IntegralUpsize Int16 Int64 
IntegralUpsize Int32 Int 

Methods

integralUpsize :: Int32 -> Int #

IntegralUpsize Int32 Int64 
IntegralUpsize Word Word64 
IntegralUpsize Word8 Int 

Methods

integralUpsize :: Word8 -> Int #

IntegralUpsize Word8 Int16 
IntegralUpsize Word8 Int32 
IntegralUpsize Word8 Int64 
IntegralUpsize Word8 Word 

Methods

integralUpsize :: Word8 -> Word #

IntegralUpsize Word8 Word16 
IntegralUpsize Word8 Word32 
IntegralUpsize Word8 Word64 
IntegralUpsize Word16 Word 
IntegralUpsize Word16 Word32 
IntegralUpsize Word16 Word64 
IntegralUpsize Word32 Word 
IntegralUpsize Word32 Word64 
IsIntegral a => IntegralUpsize a Integer 

Methods

integralUpsize :: a -> Integer #

IsNatural a => IntegralUpsize a Natural 

Methods

integralUpsize :: a -> Natural #

class IntegralDownsize a b where #

Downsize an integral value

Minimal complete definition

integralDownsizeCheck

Methods

integralDownsize :: a -> b #

integralDownsizeCheck :: a -> Maybe b #

Instances

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

class IntegralCast a b where #

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

Methods

integralCast :: a -> b #

Evaluation

class NormalForm a where #

Data that can be fully evaluated in Normal Form

Minimal complete definition

toNormalForm

Methods

toNormalForm :: a -> () #

Instances

NormalForm Bool 

Methods

toNormalForm :: Bool -> () #

NormalForm Char 

Methods

toNormalForm :: Char -> () #

NormalForm Double 

Methods

toNormalForm :: Double -> () #

NormalForm Float 

Methods

toNormalForm :: Float -> () #

NormalForm Int 

Methods

toNormalForm :: Int -> () #

NormalForm Int8 

Methods

toNormalForm :: Int8 -> () #

NormalForm Int16 

Methods

toNormalForm :: Int16 -> () #

NormalForm Int32 

Methods

toNormalForm :: Int32 -> () #

NormalForm Int64 

Methods

toNormalForm :: Int64 -> () #

NormalForm Integer 

Methods

toNormalForm :: Integer -> () #

NormalForm Word 

Methods

toNormalForm :: Word -> () #

NormalForm Word8 

Methods

toNormalForm :: Word8 -> () #

NormalForm Word16 

Methods

toNormalForm :: Word16 -> () #

NormalForm Word32 

Methods

toNormalForm :: Word32 -> () #

NormalForm Word64 

Methods

toNormalForm :: Word64 -> () #

NormalForm () 

Methods

toNormalForm :: () -> () #

NormalForm Natural 

Methods

toNormalForm :: Natural -> () #

NormalForm CChar 

Methods

toNormalForm :: CChar -> () #

NormalForm CSChar 

Methods

toNormalForm :: CSChar -> () #

NormalForm CUChar 

Methods

toNormalForm :: CUChar -> () #

NormalForm CShort 

Methods

toNormalForm :: CShort -> () #

NormalForm CUShort 

Methods

toNormalForm :: CUShort -> () #

NormalForm CInt 

Methods

toNormalForm :: CInt -> () #

NormalForm CUInt 

Methods

toNormalForm :: CUInt -> () #

NormalForm CLong 

Methods

toNormalForm :: CLong -> () #

NormalForm CULong 

Methods

toNormalForm :: CULong -> () #

NormalForm CLLong 

Methods

toNormalForm :: CLLong -> () #

NormalForm CULLong 

Methods

toNormalForm :: CULLong -> () #

NormalForm CFloat 

Methods

toNormalForm :: CFloat -> () #

NormalForm CDouble 

Methods

toNormalForm :: CDouble -> () #

NormalForm String 

Methods

toNormalForm :: String -> () #

NormalForm Word256 

Methods

toNormalForm :: Word256 -> () #

NormalForm Word128 

Methods

toNormalForm :: Word128 -> () #

NormalForm Char7 

Methods

toNormalForm :: Char7 -> () #

NormalForm IPv4 # 

Methods

toNormalForm :: IPv4 -> () #

NormalForm IPv6 # 

Methods

toNormalForm :: IPv6 -> () #

NormalForm UUID # 

Methods

toNormalForm :: UUID -> () #

NormalForm a => NormalForm [a] 

Methods

toNormalForm :: [a] -> () #

NormalForm a => NormalForm (Maybe a) 

Methods

toNormalForm :: Maybe a -> () #

NormalForm (Ptr a) 

Methods

toNormalForm :: Ptr a -> () #

NormalForm a => NormalForm (Array a) 

Methods

toNormalForm :: Array a -> () #

NormalForm (UArray ty) 

Methods

toNormalForm :: UArray ty -> () #

NormalForm (Block ty) 

Methods

toNormalForm :: Block ty -> () #

NormalForm (Offset a) 

Methods

toNormalForm :: Offset a -> () #

NormalForm (CountOf a) 

Methods

toNormalForm :: CountOf a -> () #

NormalForm a => NormalForm (LE a) 

Methods

toNormalForm :: LE a -> () #

NormalForm a => NormalForm (BE a) 

Methods

toNormalForm :: BE a -> () #

NormalForm (ChunkedUArray ty) # 

Methods

toNormalForm :: ChunkedUArray ty -> () #

(NormalForm l, NormalForm r) => NormalForm (Either l r) 

Methods

toNormalForm :: Either l r -> () #

(NormalForm a, NormalForm b) => NormalForm (a, b) 

Methods

toNormalForm :: (a, b) -> () #

(NormalForm a, NormalForm b) => NormalForm (These a b) 

Methods

toNormalForm :: These a b -> () #

(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) # 

Methods

toNormalForm :: Tuple2 a b -> () #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (a, b, c) 

Methods

toNormalForm :: (a, b, c) -> () #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) # 

Methods

toNormalForm :: Tuple3 a b c -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (a, b, c, d) 

Methods

toNormalForm :: (a, b, c, d) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) # 

Methods

toNormalForm :: Tuple4 a b c d -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e) => NormalForm (a, b, c, d, e) 

Methods

toNormalForm :: (a, b, c, d, e) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f) => NormalForm (a, b, c, d, e, f) 

Methods

toNormalForm :: (a, b, c, d, e, f) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g) => NormalForm (a, b, c, d, e, f, g) 

Methods

toNormalForm :: (a, b, c, d, e, f, g) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g, NormalForm h) => NormalForm (a, b, c, d, e, f, g, h) 

Methods

toNormalForm :: (a, b, c, d, e, f, g, h) -> () #

force :: NormalForm a => a -> a #

deepseq :: NormalForm a => a -> b -> b #

These

data These a b :: * -> * -> * #

Either a or b or both.

Constructors

This a 
That b 
These a b 

Instances

Bifunctor These 

Methods

bimap :: (a -> b) -> (c -> d) -> These a c -> These b d #

first :: (a -> b) -> These a c -> These b c #

second :: (b -> c) -> These a b -> These a c #

Functor (These a) 

Methods

fmap :: (a -> b) -> These a a -> These a b #

(<$) :: a -> These a b -> These a a #

(Eq b, Eq a) => Eq (These a b) 

Methods

(==) :: These a b -> These a b -> Bool #

(/=) :: These a b -> These a b -> Bool #

(Ord b, Ord a) => Ord (These a b) 

Methods

compare :: These a b -> These a b -> Ordering #

(<) :: These a b -> These a b -> Bool #

(<=) :: These a b -> These a b -> Bool #

(>) :: These a b -> These a b -> Bool #

(>=) :: These a b -> These a b -> Bool #

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

(Show b, Show a) => Show (These a b) 

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(NormalForm a, NormalForm b) => NormalForm (These a b) 

Methods

toNormalForm :: These a b -> () #

Block of memory

data Block ty :: * -> * #

A block of memory containing unpacked bytes representing values of type ty

Instances

PrimType ty => IsList (Block ty) 

Associated Types

type Item (Block ty) :: * #

Methods

fromList :: [Item (Block ty)] -> Block ty #

fromListN :: Int -> [Item (Block ty)] -> Block ty #

toList :: Block ty -> [Item (Block ty)] #

(PrimType ty, Eq ty) => Eq (Block ty) 

Methods

(==) :: Block ty -> Block ty -> Bool #

(/=) :: Block ty -> Block ty -> Bool #

Data ty => Data (Block ty) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block ty -> c (Block ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Block ty) #

toConstr :: Block ty -> Constr #

dataTypeOf :: Block ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Block ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Block ty)) #

gmapT :: (forall b. Data b => b -> b) -> Block ty -> Block ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

(PrimType ty, Ord ty) => Ord (Block ty) 

Methods

compare :: Block ty -> Block ty -> Ordering #

(<) :: Block ty -> Block ty -> Bool #

(<=) :: Block ty -> Block ty -> Bool #

(>) :: Block ty -> Block ty -> Bool #

(>=) :: Block ty -> Block ty -> Bool #

max :: Block ty -> Block ty -> Block ty #

min :: Block ty -> Block ty -> Block ty #

(PrimType ty, Show ty) => Show (Block ty) 

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

PrimType ty => Monoid (Block ty) 

Methods

mempty :: Block ty #

mappend :: Block ty -> Block ty -> Block ty #

mconcat :: [Block ty] -> Block ty #

NormalForm (Block ty) 

Methods

toNormalForm :: Block ty -> () #

PrimType ty => Fold1able (Block ty) # 

Methods

foldl1' :: (Element (Block ty) -> Element (Block ty) -> Element (Block ty)) -> NonEmpty (Block ty) -> Element (Block ty) #

foldr1 :: (Element (Block ty) -> Element (Block ty) -> Element (Block ty)) -> NonEmpty (Block ty) -> Element (Block ty) #

PrimType ty => Foldable (Block ty) # 

Methods

foldl' :: (a -> Element (Block ty) -> a) -> a -> Block ty -> a #

foldr :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a #

foldr' :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a #

PrimType ty => IndexedCollection (Block ty) # 

Methods

(!) :: Block ty -> Offset (Element (Block ty)) -> Maybe (Element (Block ty)) #

findIndex :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Offset (Element (Block ty))) #

PrimType ty => Copy (Block ty) # 

Methods

copy :: Block ty -> Block ty #

PrimType ty => Collection (Block ty) # 

Methods

null :: Block ty -> Bool #

length :: Block ty -> CountOf (Element (Block ty)) #

elem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool #

notElem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool #

maximum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) #

minimum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) #

any :: (Element (Block ty) -> Bool) -> Block ty -> Bool #

all :: (Element (Block ty) -> Bool) -> Block ty -> Bool #

PrimType ty => Sequential (Block ty) # 

Methods

take :: CountOf (Element (Block ty)) -> Block ty -> Block ty #

revTake :: CountOf (Element (Block ty)) -> Block ty -> Block ty #

drop :: CountOf (Element (Block ty)) -> Block ty -> Block ty #

revDrop :: CountOf (Element (Block ty)) -> Block ty -> Block ty #

splitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) #

revSplitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) #

splitOn :: (Element (Block ty) -> Bool) -> Block ty -> [Block ty] #

break :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) #

breakEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) #

breakElem :: Element (Block ty) -> Block ty -> (Block ty, Block ty) #

takeWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty #

dropWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty #

intersperse :: Element (Block ty) -> Block ty -> Block ty #

intercalate :: Element (Block ty) -> Block ty -> Element (Block ty) #

span :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) #

spanEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) #

filter :: (Element (Block ty) -> Bool) -> Block ty -> Block ty #

partition :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) #

reverse :: Block ty -> Block ty #

uncons :: Block ty -> Maybe (Element (Block ty), Block ty) #

unsnoc :: Block ty -> Maybe (Block ty, Element (Block ty)) #

snoc :: Block ty -> Element (Block ty) -> Block ty #

cons :: Element (Block ty) -> Block ty -> Block ty #

find :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Element (Block ty)) #

sortBy :: (Element (Block ty) -> Element (Block ty) -> Ordering) -> Block ty -> Block ty #

singleton :: Element (Block ty) -> Block ty #

head :: NonEmpty (Block ty) -> Element (Block ty) #

last :: NonEmpty (Block ty) -> Element (Block ty) #

tail :: NonEmpty (Block ty) -> Block ty #

init :: NonEmpty (Block ty) -> Block ty #

replicate :: CountOf (Element (Block ty)) -> Element (Block ty) -> Block ty #

isPrefixOf :: Block ty -> Block ty -> Bool #

isSuffixOf :: Block ty -> Block ty -> Bool #

isInfixOf :: Block ty -> Block ty -> Bool #

stripPrefix :: Block ty -> Block ty -> Maybe (Block ty) #

stripSuffix :: Block ty -> Block ty -> Maybe (Block ty) #

type Item (Block ty) 
type Item (Block ty) = ty
type Element (Block ty) # 
type Element (Block ty) = ty

data MutableBlock ty st :: * -> * -> * #

A Mutable block of memory containing unpacked bytes representing values of type ty

Instances

PrimType ty => MutableCollection (MutableBlock ty) # 

Associated Types

type MutableFreezed (MutableBlock ty :: * -> *) :: * #

type MutableKey (MutableBlock ty :: * -> *) :: * #

type MutableValue (MutableBlock ty :: * -> *) :: * #

type MutableFreezed (MutableBlock ty) # 
type MutableKey (MutableBlock ty) # 
type MutableValue (MutableBlock ty) # 
type MutableValue (MutableBlock ty) = ty

Ascii

data Char7 :: * #

ASCII value between 0x0 and 0x7f

newtype AsciiString :: * #

Opaque packed array of characters in the ASCII encoding

Constructors

AsciiString 

Fields

Instances

IsList AsciiString 
Eq AsciiString 
Ord AsciiString 
Show AsciiString 
IsString AsciiString 
Monoid AsciiString 
Collection AsciiString # 
Sequential AsciiString # 

Methods

take :: CountOf (Element AsciiString) -> AsciiString -> AsciiString #

revTake :: CountOf (Element AsciiString) -> AsciiString -> AsciiString #

drop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString #

revDrop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString #

splitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) #

revSplitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) #

splitOn :: (Element AsciiString -> Bool) -> AsciiString -> [AsciiString] #

break :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) #

breakEnd :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) #

breakElem :: Element AsciiString -> AsciiString -> (AsciiString, AsciiString) #

takeWhile :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString #

dropWhile :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString #

intersperse :: Element AsciiString -> AsciiString -> AsciiString #

intercalate :: Element AsciiString -> AsciiString -> Element AsciiString #

span :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) #

spanEnd :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) #

filter :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString #

partition :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) #

reverse :: AsciiString -> AsciiString #

uncons :: AsciiString -> Maybe (Element AsciiString, AsciiString) #

unsnoc :: AsciiString -> Maybe (AsciiString, Element AsciiString) #

snoc :: AsciiString -> Element AsciiString -> AsciiString #

cons :: Element AsciiString -> AsciiString -> AsciiString #

find :: (Element AsciiString -> Bool) -> AsciiString -> Maybe (Element AsciiString) #

sortBy :: (Element AsciiString -> Element AsciiString -> Ordering) -> AsciiString -> AsciiString #

singleton :: Element AsciiString -> AsciiString #

head :: NonEmpty AsciiString -> Element AsciiString #

last :: NonEmpty AsciiString -> Element AsciiString #

tail :: NonEmpty AsciiString -> AsciiString #

init :: NonEmpty AsciiString -> AsciiString #

replicate :: CountOf (Element AsciiString) -> Element AsciiString -> AsciiString #

isPrefixOf :: AsciiString -> AsciiString -> Bool #

isSuffixOf :: AsciiString -> AsciiString -> Bool #

isInfixOf :: AsciiString -> AsciiString -> Bool #

stripPrefix :: AsciiString -> AsciiString -> Maybe AsciiString #

stripSuffix :: AsciiString -> AsciiString -> Maybe AsciiString #

Zippable AsciiString # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element AsciiString) -> a -> b -> AsciiString #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element AsciiString) -> a -> b -> c -> AsciiString #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element AsciiString) -> a -> b -> c -> d -> AsciiString #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element AsciiString) -> a -> b -> c -> d -> e -> AsciiString #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element AsciiString) -> a -> b -> c -> d -> e -> f -> AsciiString #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element AsciiString) -> a -> b -> c -> d -> e -> f -> g -> AsciiString #

Arbitrary AsciiString # 
type Item AsciiString 
type Element AsciiString #