License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A Nat-sized version of Block
Synopsis
- data BlockN (n :: Nat) a
- data MutableBlockN (n :: Nat) ty st
- length :: forall n ty. (KnownNat n, Countable ty n) => BlockN n ty -> CountOf ty
- lengthBytes :: forall n ty. PrimType ty => BlockN n ty -> CountOf Word8
- toBlockN :: forall n ty. (PrimType ty, KnownNat n, Countable ty n) => Block ty -> Maybe (BlockN n ty)
- toBlock :: BlockN n ty -> Block ty
- new :: forall n ty prim. (PrimType ty, KnownNat n, Countable ty n, PrimMonad prim) => prim (MutableBlockN n ty (PrimState prim))
- newPinned :: forall n ty prim. (PrimType ty, KnownNat n, Countable ty n, PrimMonad prim) => prim (MutableBlockN n ty (PrimState prim))
- singleton :: PrimType ty => ty -> BlockN 1 ty
- replicate :: forall n ty. (KnownNat n, Countable ty n, PrimType ty) => ty -> BlockN n ty
- thaw :: (KnownNat n, PrimMonad prim, PrimType ty) => BlockN n ty -> prim (MutableBlockN n ty (PrimState prim))
- freeze :: (PrimMonad prim, PrimType ty, Countable ty n) => MutableBlockN n ty (PrimState prim) -> prim (BlockN n ty)
- index :: forall i n ty. PrimType ty => BlockN n ty -> Offset ty -> ty
- indexStatic :: forall i n ty. (KnownNat i, CmpNat i n ~ 'LT, PrimType ty, Offsetable ty i) => BlockN n ty -> ty
- map :: (PrimType a, PrimType b) => (a -> b) -> BlockN n a -> BlockN n b
- foldl' :: PrimType ty => (a -> ty -> a) -> a -> BlockN n ty -> a
- foldr :: PrimType ty => (ty -> a -> a) -> a -> BlockN n ty -> a
- cons :: PrimType ty => ty -> BlockN n ty -> BlockN (n + 1) ty
- snoc :: PrimType ty => BlockN n ty -> ty -> BlockN (n + 1) ty
- elem :: PrimType ty => ty -> BlockN n ty -> Bool
- sub :: forall i j n ty. ((i <=? n) ~ 'True, (j <=? n) ~ 'True, (i <=? j) ~ 'True, PrimType ty, KnownNat i, KnownNat j, Offsetable ty i, Offsetable ty j) => BlockN n ty -> BlockN (j - i) ty
- uncons :: forall n ty. (CmpNat 0 n ~ 'LT, PrimType ty, KnownNat n, Offsetable ty n) => BlockN n ty -> (ty, BlockN (n - 1) ty)
- unsnoc :: forall n ty. (CmpNat 0 n ~ 'LT, KnownNat n, PrimType ty, Offsetable ty n) => BlockN n ty -> (BlockN (n - 1) ty, ty)
- splitAt :: forall i n ty. (CmpNat i n ~ 'LT, PrimType ty, KnownNat i, Countable ty i) => BlockN n ty -> (BlockN i ty, BlockN (n - i) ty)
- all :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool
- any :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool
- find :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Maybe ty
- reverse :: PrimType ty => BlockN n ty -> BlockN n ty
- sortBy :: PrimType ty => (ty -> ty -> Ordering) -> BlockN n ty -> BlockN n ty
- intersperse :: (CmpNat n 1 ~ 'GT, PrimType ty) => ty -> BlockN n ty -> BlockN ((n + n) - 1) ty
- withPtr :: (PrimMonad prim, KnownNat n) => BlockN n ty -> (Ptr ty -> prim a) -> prim a
- withMutablePtr :: (PrimMonad prim, KnownNat n) => MutableBlockN n ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- withMutablePtrHint :: forall n ty prim a. (PrimMonad prim, KnownNat n) => Bool -> Bool -> MutableBlockN n ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- cast :: forall n m a b. (PrimType a, PrimType b, KnownNat n, KnownNat m, (PrimSize b * m) ~ (PrimSize a * n)) => BlockN n a -> BlockN m b
- mutableCast :: forall n m a b st. (PrimType a, PrimType b, KnownNat n, KnownNat m, (PrimSize b * m) ~ (PrimSize a * n)) => MutableBlockN n a st -> MutableBlockN m b st
Documentation
data BlockN (n :: Nat) a Source #
Sized version of Block
Instances
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) Source # | |
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Array ty) (BlockN n ty) Source # | |
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) Source # | |
(KnownNat n, Data a) => Data (BlockN n a) Source # | |
Defined in Basement.Sized.Block gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockN n a -> c (BlockN n a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BlockN n a) # toConstr :: BlockN n a -> Constr # dataTypeOf :: BlockN n a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BlockN n a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BlockN n a)) # gmapT :: (forall b. Data b => b -> b) -> BlockN n a -> BlockN n a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockN n a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockN n a -> r # gmapQ :: (forall d. Data d => d -> u) -> BlockN n a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockN n a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockN n a -> m (BlockN n a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockN n a -> m (BlockN n a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockN n a -> m (BlockN n a) # | |
(PrimType a, Show a) => Show (BlockN n a) Source # | |
NormalForm (BlockN n a) Source # | |
Defined in Basement.Sized.Block toNormalForm :: BlockN n a -> () Source # | |
PrimType a => Eq (BlockN n a) Source # | |
(PrimType a, Ord a) => Ord (BlockN n a) Source # | |
From (BlockN n ty) (Block ty) Source # | |
(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (Array ty) Source # | |
(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) Source # | |
(PrimType a, PrimType b, KnownNat n, KnownNat m, (PrimSize b * m) ~ (PrimSize a * n)) => From (BlockN n a) (BlockN m b) Source # | |
data MutableBlockN (n :: Nat) ty st Source #
toBlockN :: forall n ty. (PrimType ty, KnownNat n, Countable ty n) => Block ty -> Maybe (BlockN n ty) Source #
new :: forall n ty prim. (PrimType ty, KnownNat n, Countable ty n, PrimMonad prim) => prim (MutableBlockN n ty (PrimState prim)) Source #
Create a new unpinned mutable block of a specific N size of ty
elements
If the size exceeds a GHC-defined threshold, then the memory will be
pinned. To be certain about pinning status with small size, use newPinned
newPinned :: forall n ty prim. (PrimType ty, KnownNat n, Countable ty n, PrimMonad prim) => prim (MutableBlockN n ty (PrimState prim)) Source #
Create a new pinned mutable block of a specific N size of ty
elements
thaw :: (KnownNat n, PrimMonad prim, PrimType ty) => BlockN n ty -> prim (MutableBlockN n ty (PrimState prim)) Source #
freeze :: (PrimMonad prim, PrimType ty, Countable ty n) => MutableBlockN n ty (PrimState prim) -> prim (BlockN n ty) Source #
indexStatic :: forall i n ty. (KnownNat i, CmpNat i n ~ 'LT, PrimType ty, Offsetable ty i) => BlockN n ty -> ty Source #
sub :: forall i j n ty. ((i <=? n) ~ 'True, (j <=? n) ~ 'True, (i <=? j) ~ 'True, PrimType ty, KnownNat i, KnownNat j, Offsetable ty i, Offsetable ty j) => BlockN n ty -> BlockN (j - i) ty Source #
uncons :: forall n ty. (CmpNat 0 n ~ 'LT, PrimType ty, KnownNat n, Offsetable ty n) => BlockN n ty -> (ty, BlockN (n - 1) ty) Source #
unsnoc :: forall n ty. (CmpNat 0 n ~ 'LT, KnownNat n, PrimType ty, Offsetable ty n) => BlockN n ty -> (BlockN (n - 1) ty, ty) Source #
splitAt :: forall i n ty. (CmpNat i n ~ 'LT, PrimType ty, KnownNat i, Countable ty i) => BlockN n ty -> (BlockN i ty, BlockN (n - i) ty) Source #
intersperse :: (CmpNat n 1 ~ 'GT, PrimType ty) => ty -> BlockN n ty -> BlockN ((n + n) - 1) ty Source #
withPtr :: (PrimMonad prim, KnownNat n) => BlockN n ty -> (Ptr ty -> prim a) -> prim a Source #
Get a Ptr pointing to the data in the Block.
Since a Block is immutable, this Ptr shouldn't be to use to modify the contents
If the Block is pinned, then its address is returned as is, however if it's unpinned, a pinned copy of the Block is made before getting the address.
withMutablePtr :: (PrimMonad prim, KnownNat n) => MutableBlockN n ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #
Create a pointer on the beginning of the MutableBlock
and call a function f
.
The mutable block can be mutated by the f
function
and the change will be reflected in the mutable block
If the mutable block is unpinned, a trampoline buffer
is created and the data is only copied when f
return.
it is all-in-all highly inefficient as this cause 2 copies
:: forall n ty prim a. (PrimMonad prim, KnownNat n) | |
=> Bool | hint that the buffer doesn't need to have the same value as the mutable block when calling f |
-> Bool | hint that the buffer is not supposed to be modified by call of f |
-> MutableBlockN n ty (PrimState prim) | |
-> (Ptr ty -> prim a) | |
-> prim a |
Same as withMutablePtr
but allow to specify 2 optimisations
which is only useful when the MutableBlock is unpinned and need
a pinned trampoline to be called safely.
If skipCopy is True, then the first copy which happen before
the call to f
, is skipped. The Ptr is now effectively
pointing to uninitialized data in a new mutable Block.
If skipCopyBack is True, then the second copy which happen after
the call to f
, is skipped. Then effectively in the case of a
trampoline being used the memory changed by f
will not
be reflected in the original Mutable Block.
If using the wrong parameters, it will lead to difficult to debug issue of corrupted buffer which only present themselves with certain Mutable Block that happened to have been allocated unpinned.
If unsure use withMutablePtr
, which default to *not* skip
any copy.
cast :: forall n m a b. (PrimType a, PrimType b, KnownNat n, KnownNat m, (PrimSize b * m) ~ (PrimSize a * n)) => BlockN n a -> BlockN m b Source #
mutableCast :: forall n m a b st. (PrimType a, PrimType b, KnownNat n, KnownNat m, (PrimSize b * m) ~ (PrimSize a * n)) => MutableBlockN n a st -> MutableBlockN m b st Source #