License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Foundation.Primitive
Description
Synopsis
- class Eq ty => PrimType ty where
- type PrimSize ty :: Nat
- primSizeInBytes :: Proxy ty -> CountOf Word8
- primShiftToBytes :: Proxy ty -> Int
- primBaUIndex :: ByteArray# -> Offset ty -> ty
- primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty
- primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim ()
- primAddrIndex :: Addr# -> Offset ty -> ty
- primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty
- primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim ()
- class (Functor m, Applicative m, Monad m) => PrimMonad (m :: Type -> Type) where
- type PrimState (m :: Type -> Type)
- type PrimVar (m :: Type -> Type) :: Type -> Type
- primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
- primThrow :: Exception e => e -> m a
- unPrimMonad :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
- primVarNew :: a -> m (PrimVar m a)
- primVarRead :: PrimVar m a -> m a
- primVarWrite :: PrimVar m a -> a -> m ()
- class ByteSwap a
- newtype LE a = LE {
- unLE :: a
- toLE :: ByteSwap a => a -> LE a
- fromLE :: ByteSwap a => LE a -> a
- newtype BE a = BE {
- unBE :: a
- toBE :: ByteSwap a => a -> BE a
- fromBE :: ByteSwap a => BE a -> a
- class IntegralUpsize a b where
- integralUpsize :: a -> b
- class IntegralDownsize a b where
- integralDownsize :: a -> b
- integralDownsizeCheck :: a -> Maybe b
- class NormalForm a where
- toNormalForm :: a -> ()
- force :: NormalForm a => a -> a
- deepseq :: NormalForm a => a -> b -> b
- data These a b
- data Block ty
- data MutableBlock ty st
- data Char7
- data AsciiString
Documentation
class Eq ty => PrimType ty where #
Methods
primSizeInBytes :: Proxy ty -> CountOf Word8 #
primShiftToBytes :: Proxy ty -> Int #
primBaUIndex :: ByteArray# -> Offset ty -> ty #
primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty #
primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () #
primAddrIndex :: Addr# -> Offset ty -> ty #
primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty #
primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () #
Instances
class (Functor m, Applicative m, Monad m) => PrimMonad (m :: Type -> Type) where #
Methods
primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a #
primThrow :: Exception e => e -> m a #
unPrimMonad :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #) #
primVarNew :: a -> m (PrimVar m a) #
primVarRead :: PrimVar m a -> m a #
primVarWrite :: PrimVar m a -> a -> m () #
Instances
PrimMonad IO | |
Defined in Basement.Monad Methods primitive :: (State# (PrimState IO) -> (# State# (PrimState IO), a #)) -> IO a # primThrow :: Exception e => e -> IO a # unPrimMonad :: IO a -> State# (PrimState IO) -> (# State# (PrimState IO), a #) # primVarNew :: a -> IO (PrimVar IO a) # primVarRead :: PrimVar IO a -> IO a # primVarWrite :: PrimVar IO a -> a -> IO () # | |
PrimMonad (ST s) | |
Defined in Basement.Monad Methods primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a # primThrow :: Exception e => e -> ST s a # unPrimMonad :: ST s a -> State# (PrimState (ST s)) -> (# 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
Minimal complete definition
byteSwap
Instances
Instances
Integral convertion
class IntegralUpsize a b where #
Methods
integralUpsize :: a -> b #
Instances
class IntegralDownsize a b where #
Minimal complete definition
Instances
Evaluation
class NormalForm a where #
Methods
toNormalForm :: a -> () #
Instances
force :: NormalForm a => a -> a #
deepseq :: NormalForm a => a -> b -> b #
These
Instances
Bifunctor These | |
Functor (These a) | |
(Show a, Show b) => Show (These a b) | |
(NormalForm a, NormalForm b) => NormalForm (These a b) | |
Defined in Basement.These Methods toNormalForm :: These a b -> () # | |
(Eq a, Eq b) => Eq (These a b) | |
(Ord a, Ord b) => Ord (These a b) | |
From (Either a b) (These a b) | |
Defined in Basement.From |
Block of memory
Instances
Data ty => Data (Block ty) | |
Defined in Basement.Block.Base 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 :: forall r r'. (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 => Monoid (Block ty) | |
PrimType ty => Semigroup (Block ty) | |
PrimType ty => IsList (Block ty) | |
(PrimType ty, Show ty) => Show (Block ty) | |
NormalForm (Block ty) | |
Defined in Basement.Block.Base Methods toNormalForm :: Block ty -> () # | |
PrimType ty => Collection (Block ty) Source # | |
Defined in Foundation.Collection.Collection Methods null :: Block ty -> Bool Source # length :: Block ty -> CountOf (Element (Block ty)) Source # elem :: (Eq a, a ~ Element (Block ty)) => Element (Block ty) -> Block ty -> Bool Source # notElem :: (Eq a, a ~ Element (Block ty)) => Element (Block ty) -> Block ty -> Bool Source # maximum :: (Ord a, a ~ Element (Block ty)) => NonEmpty (Block ty) -> Element (Block ty) Source # minimum :: (Ord a, a ~ Element (Block ty)) => NonEmpty (Block ty) -> Element (Block ty) Source # any :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source # all :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source # | |
PrimType ty => Copy (Block ty) Source # | |
PrimType ty => Fold1able (Block ty) Source # | |
Defined in Foundation.Collection.Foldable | |
PrimType ty => Foldable (Block ty) Source # | |
PrimType ty => IndexedCollection (Block ty) Source # | |
PrimType ty => Sequential (Block ty) Source # | |
Defined in Foundation.Collection.Sequential Methods take :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source # revTake :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source # drop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source # revDrop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source # splitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source # revSplitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source # splitOn :: (Element (Block ty) -> Bool) -> Block ty -> [Block ty] Source # break :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source # breakEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source # breakElem :: Element (Block ty) -> Block ty -> (Block ty, Block ty) Source # takeWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source # dropWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source # intersperse :: Element (Block ty) -> Block ty -> Block ty Source # intercalate :: Element (Block ty) -> Block ty -> Element (Block ty) Source # span :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source # spanEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source # filter :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source # partition :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source # reverse :: Block ty -> Block ty Source # uncons :: Block ty -> Maybe (Element (Block ty), Block ty) Source # unsnoc :: Block ty -> Maybe (Block ty, Element (Block ty)) Source # snoc :: Block ty -> Element (Block ty) -> Block ty Source # cons :: Element (Block ty) -> Block ty -> Block ty Source # find :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Element (Block ty)) Source # sortBy :: (Element (Block ty) -> Element (Block ty) -> Ordering) -> Block ty -> Block ty Source # singleton :: Element (Block ty) -> Block ty Source # head :: NonEmpty (Block ty) -> Element (Block ty) Source # last :: NonEmpty (Block ty) -> Element (Block ty) Source # tail :: NonEmpty (Block ty) -> Block ty Source # init :: NonEmpty (Block ty) -> Block ty Source # replicate :: CountOf (Element (Block ty)) -> Element (Block ty) -> Block ty Source # isPrefixOf :: Block ty -> Block ty -> Bool Source # isSuffixOf :: Block ty -> Block ty -> Bool Source # isInfixOf :: Block ty -> Block ty -> Bool Source # stripPrefix :: Block ty -> Block ty -> Maybe (Block ty) Source # stripSuffix :: Block ty -> Block ty -> Maybe (Block ty) Source # | |
(PrimType ty, Eq ty) => Eq (Block ty) | |
(PrimType ty, Ord ty) => Ord (Block ty) | |
Defined in Basement.Block.Base | |
Cast (Block a) (Block Word8) | |
Defined in Basement.Cast | |
PrimType ty => From (Block ty) (UArray ty) | |
Defined in Basement.From | |
PrimType ty => From (Array ty) (Block ty) | |
Defined in Basement.From | |
PrimType ty => From (UArray ty) (Block ty) | |
Defined in Basement.From | |
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) | |
Defined in Basement.From | |
From (BlockN n ty) (Block ty) | |
Defined in Basement.From | |
type Item (Block ty) | |
Defined in Basement.Block.Base | |
type Element (Block ty) Source # | |
Defined in Foundation.Collection.Element |
data MutableBlock ty st #
Instances
Ascii
Instances
Show Char7 | |
NormalForm Char7 | |
Defined in Basement.NormalForm Methods toNormalForm :: Char7 -> () # | |
PrimType Char7 | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Char7 -> CountOf Word8 # primShiftToBytes :: Proxy Char7 -> Int # primBaUIndex :: ByteArray# -> Offset Char7 -> Char7 # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char7 -> prim Char7 # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char7 -> Char7 -> prim () # primAddrIndex :: Addr# -> Offset Char7 -> Char7 # primAddrRead :: PrimMonad prim => Addr# -> Offset Char7 -> prim Char7 # primAddrWrite :: PrimMonad prim => Addr# -> Offset Char7 -> Char7 -> prim () # | |
Arbitrary Char7 Source # | |
Eq Char7 | |
Ord Char7 | |
type NatNumMaxBound Char7 | |
Defined in Basement.Nat type NatNumMaxBound Char7 = 127 | |
type PrimSize Char7 | |
Defined in Basement.PrimType |
data AsciiString #