foundation-0.0.9: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerHaskell Foundation
Safe HaskellNone
LanguageHaskell2010

Foundation.Primitive.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 Size, 1 Pinning status trimmed
  • It's unpackable in any constructor
  • It uses unpinned memory by default

Synopsis

Documentation

data Block ty Source #

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

Constructors

Block ByteArray# 

Instances

PrimType ty => IsList (Block ty) Source # 

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) Source # 

Methods

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

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

Data ty => Data (Block ty) Source # 

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) Source # 

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) Source # 

Methods

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

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

PrimType ty => Monoid (Block ty) Source # 

Methods

mempty :: Block ty #

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

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

NormalForm (Block ty) Source # 

Methods

toNormalForm :: Block ty -> () Source #

PrimType ty => Copy (Block ty) Source # 

Methods

copy :: Block ty -> Block ty Source #

PrimType ty => Collection (Block ty) Source # 

Methods

null :: Block ty -> Bool Source #

length :: Block ty -> Int 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 => Foldable (Block ty) Source # 

Methods

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

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

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

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

PrimType ty => IndexedCollection (Block ty) Source # 

Methods

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

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

PrimType ty => Sequential (Block ty) Source # 

Methods

take :: Int -> Block ty -> Block ty Source #

revTake :: Int -> Block ty -> Block ty Source #

drop :: Int -> Block ty -> Block ty Source #

revDrop :: Int -> Block ty -> Block ty Source #

splitAt :: Int -> Block ty -> (Block ty, Block ty) Source #

revSplitAt :: Int -> 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 #

breakElem :: Element (Block ty) -> Block ty -> (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 #

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 :: Word -> Element (Block ty) -> Block ty Source #

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

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

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

data MutableBlock ty st Source #

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

Constructors

MutableBlock (MutableByteArray# st) 

Instances

PrimType ty => MutableCollection (MutableBlock ty) Source # 
type MutableFreezed (MutableBlock ty) Source # 
type MutableKey (MutableBlock ty) Source # 
type MutableValue (MutableBlock ty) Source # 
type MutableValue (MutableBlock ty) = ty

Properties

length :: PrimType ty => Block ty -> Int Source #

return the number of elements of the array.

lengthSize :: forall ty. PrimType ty => Block ty -> Size ty Source #

Lowlevel functions

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

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) Source #

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 Source #

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)) Source #

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) Source #

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

Copy every cells of an existing Block to a new Block

safer api

create Source #

Arguments

:: PrimType ty 
=> Size 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 Source #

replicate :: PrimType ty => Word -> ty -> Block ty Source #

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

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 Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Foreign interfaces

unsafeCopyToPtr Source #

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