basement-0.0.10: Foundation scrap box of array & string

LicenseBSD-style
MaintainerHaskell Foundation
Safe HaskellNone
LanguageHaskell2010

Basement.Block

Contents

Description

A block of memory that contains elements of a type, very similar to an unboxed array but with the key difference:

  • It doesn't have slicing capability (no cheap take or drop)
  • It consume less memory: 1 Offset, 1 CountOf
  • It's unpackable in any constructor
  • It uses unpinned memory by default
Synopsis

Documentation

data Block ty #

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

Constructors

Block ByteArray# 
Instances
PrimType ty => IsList (Block ty) # 
Instance details

Defined in Basement.Block.Base

Associated Types

type Item (Block ty) :: Type #

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) # 
Instance details

Defined in Basement.Block.Base

Methods

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

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

Data ty => Data (Block ty) # 
Instance details

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 :: (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) # 
Instance details

Defined in Basement.Block.Base

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) # 
Instance details

Defined in Basement.Block.Base

Methods

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

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

PrimType ty => Semigroup (Block ty) # 
Instance details

Defined in Basement.Block.Base

Methods

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

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

stimes :: Integral b => b -> Block ty -> Block ty #

PrimType ty => Monoid (Block ty) # 
Instance details

Defined in Basement.Block.Base

Methods

mempty :: Block ty #

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

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

NormalForm (Block ty) # 
Instance details

Defined in Basement.Block.Base

Methods

toNormalForm :: Block ty -> () #

Cast (Block a) (Block Word8) # 
Instance details

Defined in Basement.Cast

Methods

cast :: Block a -> Block Word8 #

PrimType ty => From (Block ty) (UArray ty) # 
Instance details

Defined in Basement.From

Methods

from :: Block ty -> UArray ty #

PrimType ty => From (UArray ty) (Block ty) # 
Instance details

Defined in Basement.From

Methods

from :: UArray ty -> Block ty #

PrimType ty => From (Array ty) (Block ty) # 
Instance details

Defined in Basement.From

Methods

from :: Array ty -> Block ty #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) # 
Instance details

Defined in Basement.From

Methods

tryFrom :: Block ty -> Maybe (BlockN n ty) #

From (BlockN n ty) (Block ty) # 
Instance details

Defined in Basement.From

Methods

from :: BlockN n ty -> Block ty #

type Item (Block ty) # 
Instance details

Defined in Basement.Block.Base

type Item (Block ty) = ty

data MutableBlock ty st #

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

Constructors

MutableBlock (MutableByteArray# st) 

Properties

length :: forall ty. PrimType ty => Block ty -> CountOf ty #

Lowlevel functions

unsafeThaw :: (PrimType ty, PrimMonad prim) => Block ty -> prim (MutableBlock ty (PrimState prim)) #

Thaw an immutable block.

If the immutable block is modified, then the original immutable block will be modified too, but lead to unexpected results when querying

unsafeFreeze :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Block ty) #

Freeze a mutable block into a block.

If the mutable block is still use after freeze, then the modification will be reflected in an unexpected way in the Block.

unsafeIndex :: forall ty. PrimType ty => Block ty -> Offset ty -> ty #

Return the element at a specific index from an array without bounds checking.

Reading from invalid memory can return unpredictable and invalid values. use index if unsure.

thaw :: (PrimMonad prim, PrimType ty) => Block ty -> prim (MutableBlock ty (PrimState prim)) #

Thaw a Block into a MutableBlock

the Block is not modified, instead a new Mutable Block is created and its content is copied to the mutable block

freeze :: (PrimType ty, PrimMonad prim) => MutableBlock ty (PrimState prim) -> prim (Block ty) #

Freeze a MutableBlock into a Block, copying all the data

If the data is modified in the mutable block after this call, then the immutable Block resulting is not impacted.

copy :: PrimType ty => Block ty -> Block ty #

Copy every cells of an existing Block to a new Block

unsafeCast :: PrimType b => Block a -> Block b #

Unsafely recast an UArray containing a to an UArray containing b

The offset and size are converted from units of a to units of b, but no check are performed to make sure this is compatible.

use cast if unsure.

cast :: forall a b. (PrimType a, PrimType b) => Block a -> Block b #

Cast a Block of a to a Block of b

The requirement is that the size of type a need to be a multiple or dividend of the size of type b.

If this requirement is not met, the InvalidRecast exception is thrown

safer api

create #

Arguments

:: PrimType ty 
=> CountOf ty

the size of the block (in element of ty)

-> (Offset ty -> ty)

the function that set the value at the index

-> Block ty

the array created

Create a new array of size n by settings each cells through the function f.

singleton :: PrimType ty => ty -> Block ty #

replicate :: PrimType ty => CountOf ty -> ty -> Block ty #

index :: PrimType ty => Block ty -> Offset ty -> ty #

Return the element at a specific index from an array.

If the index @n is out of bounds, an error is raised.

map :: (PrimType a, PrimType b) => (a -> b) -> Block a -> Block b #

Map all element a from a block to a new block of b

foldl' :: PrimType ty => (a -> ty -> a) -> a -> Block ty -> a #

foldr :: PrimType ty => (ty -> a -> a) -> a -> Block ty -> a #

foldl1' :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (Block ty) -> ty #

foldr1 :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (Block ty) -> ty #

cons :: PrimType ty => ty -> Block ty -> Block ty #

snoc :: PrimType ty => Block ty -> ty -> Block ty #

uncons :: PrimType ty => Block ty -> Maybe (ty, Block ty) #

unsnoc :: PrimType ty => Block ty -> Maybe (Block ty, ty) #

sub :: PrimType ty => Block ty -> Offset ty -> Offset ty -> Block ty #

splitAt :: PrimType ty => CountOf ty -> Block ty -> (Block ty, Block ty) #

revSplitAt :: PrimType ty => CountOf ty -> Block ty -> (Block ty, Block ty) #

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

break :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) #

breakEnd :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) #

span :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) #

elem :: PrimType ty => ty -> Block ty -> Bool #

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

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

find :: PrimType ty => (ty -> Bool) -> Block ty -> Maybe ty #

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

reverse :: forall ty. PrimType ty => Block ty -> Block ty #

sortBy :: PrimType ty => (ty -> ty -> Ordering) -> Block ty -> Block ty #

intersperse :: forall ty. PrimType ty => ty -> Block ty -> Block ty #

Foreign interfaces

unsafeCopyToPtr #

Arguments

:: PrimMonad prim 
=> Block ty

the source block to copy

-> Ptr ty

The destination address where the copy is going to start

-> prim () 

Copy all the block content to the memory starting at the destination address

withPtr :: PrimMonad prim => Block ty -> (Ptr ty -> prim a) -> prim a #

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.