basement-0.0.1: Foundation scrap box of array & string

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

Basement.UArray

Contents

Description

An unboxed array of primitive types

All the cells in the array are in one chunk of contiguous memory.

Synopsis

Documentation

data UArray ty Source #

An array of type built on top of GHC primitive.

The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface

Constructors

UArray !(Offset ty) !(CountOf ty) !(UArrayBackend ty) 

Instances

From AsciiString (UArray Word8) Source # 
From String (UArray Word8) Source # 
PrimType ty => IsList (UArray ty) Source # 

Associated Types

type Item (UArray ty) :: * #

Methods

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

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

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

(PrimType ty, Eq ty) => Eq (UArray ty) Source # 

Methods

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

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

Data ty => Data (UArray ty) Source # 

Methods

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

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

toConstr :: UArray ty -> Constr #

dataTypeOf :: UArray ty -> DataType #

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

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

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

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

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

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

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

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

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

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

(PrimType ty, Ord ty) => Ord (UArray ty) Source # 

Methods

compare :: UArray ty -> UArray ty -> Ordering #

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

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

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

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

max :: UArray ty -> UArray ty -> UArray ty #

min :: UArray ty -> UArray ty -> UArray ty #

(PrimType ty, Show ty) => Show (UArray ty) Source # 

Methods

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

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Monoid (UArray ty) Source # 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

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

NormalForm (UArray ty) Source # 

Methods

toNormalForm :: UArray ty -> () Source #

TryFrom (UArray Word8) String Source # 
PrimType ty => From (Block ty) (UArray ty) Source # 

Methods

from :: Block ty -> UArray ty Source #

PrimType ty => From (UArray ty) (Array ty) Source # 

Methods

from :: UArray ty -> Array ty Source #

PrimType ty => From (UArray ty) (Block ty) Source # 

Methods

from :: UArray ty -> Block ty Source #

PrimType ty => From (Array ty) (UArray ty) Source # 

Methods

from :: Array ty -> UArray ty Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) Source # 

Methods

tryFrom :: UArray ty -> Maybe (BlockN n ty) Source #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) Source # 

Methods

from :: BlockN n ty -> UArray ty Source #

type Item (UArray ty) Source # 
type Item (UArray ty) = ty

class Eq ty => PrimType ty where Source #

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

get the size in bytes of a ty element

primShiftToBytes :: Proxy ty -> Int Source #

get the shift size

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

return the element stored at a specific index

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

Read an element at an index in a mutable array

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

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

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

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

Read a value from Addr in a specific primitive monad

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

Write a value to Addr in a specific primitive monad

Instances

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

Methods

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

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

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

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

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

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

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

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

PrimType a => PrimType (LE a) Source # 

Methods

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

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

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

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

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

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

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

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

methods

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

Copy every cells of an existing array to a new array

unsafeCopyAtRO Source #

Arguments

:: (PrimMonad prim, PrimType ty) 
=> MUArray ty (PrimState prim)

destination array

-> Offset ty

offset at destination

-> UArray ty

source array

-> Offset ty

offset at source

-> CountOf ty

number of elements to copy

-> prim () 

Copy n sequential elements from the specified offset in a source array to the specified position in a destination array.

This function does not check bounds. Accessing invalid memory can return unpredictable and invalid values.

internal methods

recast :: forall a b. (PrimType a, PrimType b) => UArray a -> UArray b Source #

Recast an array of type a to an array of b

a and b need to have the same size otherwise this raise an async exception

freeze :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> prim (UArray ty) Source #

unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (UArray ty) Source #

Freeze a mutable array into an array.

the MUArray must not be changed after freezing.

thaw :: (PrimMonad prim, PrimType ty) => UArray ty -> prim (MUArray ty (PrimState prim)) Source #

Thaw an array to a mutable array.

the array is not modified, instead a new mutable array is created and every values is copied, before returning the mutable array.

unsafeThaw :: (PrimType ty, PrimMonad prim) => UArray ty -> prim (MUArray ty (PrimState prim)) Source #

Thaw an immutable array.

The UArray must not be used after thawing.

Creation

vFromListN :: forall ty. PrimType ty => CountOf ty -> [ty] -> UArray ty Source #

Make an array from a list of elements with a size hint.

The list should be of the same size as the hint, as otherwise:

  • The length of the list is smaller than the hint: the array allocated is of the size of the hint, but is sliced to only represent the valid bits
  • The length of the list is bigger than the hint: The allocated array is the size of the hint, and the list is truncated to fit.

new :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) Source #

Create a new mutable array of size @n.

When memory for a new array is allocated, we decide if that memory region should be pinned (will not be copied around by GC) or unpinned (can be moved around by GC) depending on its size.

You can change the threshold value used by setting the environment variable HS_FOUNDATION_UARRAY_UNPINNED_MAX.

create Source #

Arguments

:: PrimType ty 
=> CountOf ty

the size of the array

-> (Offset ty -> ty)

the function that set the value at the index

-> UArray ty

the array created

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

createFromIO Source #

Arguments

:: PrimType ty 
=> CountOf ty

the size of the array

-> (Ptr ty -> IO (CountOf ty))

filling function that

-> IO (UArray ty) 

Create a pinned array that is filled by a filler function (typically an IO call like hGetBuf)

createFromPtr :: PrimType ty => Ptr ty -> CountOf ty -> IO (UArray ty) Source #

Freeze a chunk of memory pointed, of specific size into a new unboxed array

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

copyToPtr Source #

Arguments

:: (PrimType ty, PrimMonad prim) 
=> UArray ty

the source array 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 :: forall ty prim a. (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a Source #

withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #

Create a pointer on the beginning of the mutable array and call a function f.

The mutable buffer can be mutated by the f function and the change will be reflected in the mutable array

If the mutable array is unpinned, a trampoline buffer is created and the data is only copied when f return.

unsafeFreezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) Source #

freezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) Source #

fromBlock :: PrimType ty => Block ty -> UArray ty Source #

Create a UArray from a Block

The block is still used by the uarray

toBlock :: PrimType ty => UArray ty -> Block ty Source #

Create a Block from a UArray.

Note that because of the slice, the destination block is re-allocated and copied, unless the slice point at the whole array

accessors

update :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty Source #

update an array by creating a new array with the updates.

the operation copy the previous array, modify it in place, then freeze it.

unsafeUpdate :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty Source #

unsafeIndex :: forall ty. PrimType ty => UArray 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.

unsafeIndexer :: (PrimMonad prim, PrimType ty) => UArray ty -> ((Offset ty -> ty) -> prim a) -> prim a Source #

unsafeDewrap :: (ByteArray# -> Offset ty -> a) -> (Ptr ty -> Offset ty -> ST s a) -> UArray ty -> a Source #

unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty Source #

read from a cell in a mutable array without bounds checking.

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

unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () Source #

write to a cell in a mutable array without bounds checking.

Writing with invalid bounds will corrupt memory and your program will become unreliable. use write if unsure.

Functions

singleton :: PrimType ty => ty -> UArray ty Source #

replicate :: PrimType ty => CountOf ty -> ty -> UArray ty Source #

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

mapIndex :: (PrimType a, PrimType b) => (Offset b -> a -> b) -> UArray a -> UArray b Source #

findIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty) Source #

revFindIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty) Source #

index :: PrimType ty => UArray 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.

take :: CountOf ty -> UArray ty -> UArray ty Source #

Take a count of elements from the array and create an array with just those elements

drop :: CountOf ty -> UArray ty -> UArray ty Source #

Drop a count of elements from the array and return the new array minus those dropped elements

splitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) Source #

Split an array into two, with a count of at most N elements in the first one and the remaining in the other.

revDrop :: CountOf ty -> UArray ty -> UArray ty Source #

Drop the N elements from the end of the array

revTake :: CountOf ty -> UArray ty -> UArray ty Source #

Take the N elements from the end of the array

revSplitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) Source #

Split an array at the N element from the end, and return the last N elements in the first part of the tuple, and whatever first elements remaining in the second

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

break :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakEnd :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

Similar to break but start the search of the breakpoint from the end

breakEnd (> 0) [1,2,3,0,0,0]

([1,2,3], [0,0,0])

breakElem :: PrimType ty => ty -> UArray ty -> (UArray ty, UArray ty) Source #

breakLine :: UArray Word8 -> Either Bool (UArray Word8, UArray Word8) Source #

Similar to breakElem specialized to split on linefeed

it either returns: * Left. no line has been found, and whether the last character is a CR * Right, a line has been found with an optional CR, and it returns the array of bytes on the left of the CR/LF, and the the array of bytes on the right of the LF.

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

indices :: PrimType ty => UArray ty -> UArray ty -> [Offset ty] Source #

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

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

spanEnd :: PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

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

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

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

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

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

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

filter :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> UArray ty Source #

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

replace :: PrimType ty => UArray ty -> UArray ty -> UArray ty -> UArray ty Source #

Replace all the occurrencies of needle with replacement in the haystack string.

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

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

foldr1 :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (UArray ty) -> ty Source #

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

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

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

foreignMem Source #

Arguments

:: PrimType ty 
=> FinalPtr ty

the start pointer with a finalizer

-> CountOf ty

the number of elements (in elements, not bytes)

-> UArray ty 

builderAppend :: (PrimType ty, PrimMonad state) => ty -> Builder (UArray ty) (MUArray ty) ty state err () Source #

builderBuild :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m err () -> m (Either err (UArray ty)) Source #

builderBuild_ :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m () () -> m (UArray ty) Source #