basement-0.0.12: Foundation scrap box of array & string
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Basement.UArray

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 #

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

Instances details
From AsciiString (UArray Word8) # 
Instance details

Defined in Basement.From

From String (UArray Word8) # 
Instance details

Defined in Basement.From

Methods

from :: String -> UArray Word8 #

PrimType ty => IsList (UArray ty) # 
Instance details

Defined in Basement.UArray.Base

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

Defined in Basement.UArray.Base

Methods

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

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

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

Defined in Basement.UArray.Base

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 :: forall r r'. (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) # 
Instance details

Defined in Basement.UArray.Base

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

Defined in Basement.UArray.Base

Methods

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

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

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

Defined in Basement.UArray.Base

Methods

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

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

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

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

Defined in Basement.UArray.Base

Methods

mempty :: UArray ty #

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

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

NormalForm (UArray ty) # 
Instance details

Defined in Basement.UArray.Base

Methods

toNormalForm :: UArray ty -> () #

TryFrom (UArray Word8) String # 
Instance details

Defined in Basement.From

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

Defined in Basement.From

Methods

from :: Block ty -> UArray ty #

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

Defined in Basement.From

Methods

from :: UArray ty -> Array 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) (UArray ty) # 
Instance details

Defined in Basement.From

Methods

from :: Array ty -> UArray ty #

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

Defined in Basement.From

Methods

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

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

Defined in Basement.From

Methods

from :: BlockN n ty -> UArray ty #

type Item (UArray ty) # 
Instance details

Defined in Basement.UArray.Base

type Item (UArray ty) = ty

class Eq ty => PrimType ty where #

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.

Associated Types

type PrimSize ty :: Nat #

type level size of the given ty

Methods

primSizeInBytes :: Proxy ty -> CountOf Word8 #

get the size in bytes of a ty element

primShiftToBytes :: Proxy ty -> Int #

get the shift size

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

return the element stored at a specific index

primMbaURead #

Arguments

:: PrimMonad prim 
=> MutableByteArray# (PrimState prim)

mutable array to read from

-> Offset ty

index of the element to retrieve

-> prim ty

the element returned

Read an element at an index in a mutable array

primMbaUWrite #

Arguments

:: PrimMonad prim 
=> MutableByteArray# (PrimState prim)

mutable array to modify

-> Offset ty

index of the element to modify

-> ty

the new value to store

-> prim () 

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

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

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 #

Read a value from Addr in a specific primitive monad

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

Write a value to Addr in a specific primitive monad

Instances

Instances details
PrimType Char # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Char :: Nat #

PrimType Double # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Double :: Nat #

PrimType Float # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Float :: Nat #

PrimType Int # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int :: Nat #

PrimType Int8 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int8 :: Nat #

PrimType Int16 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int16 :: Nat #

PrimType Int32 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int32 :: Nat #

PrimType Int64 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int64 :: Nat #

PrimType Word # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word :: Nat #

PrimType Word8 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word8 :: Nat #

PrimType Word16 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word16 :: Nat #

PrimType Word32 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word32 :: Nat #

PrimType Word64 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word64 :: Nat #

PrimType CChar # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CChar :: Nat #

PrimType CUChar # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CUChar :: Nat #

PrimType Char7 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Char7 :: Nat #

PrimType Word128 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word128 :: Nat #

PrimType Word256 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word256 :: Nat #

PrimType a => PrimType (BE a) # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize (BE a) :: Nat #

Methods

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

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

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

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

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

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

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

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

PrimType a => PrimType (LE a) # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize (LE a) :: Nat #

Methods

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

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

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

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

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

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

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

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

methods

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

Copy every cells of an existing array to a new array

unsafeCopyAtRO #

Arguments

:: forall prim ty. (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 #

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

unsafeRecast :: (PrimType a, PrimType b) => UArray a -> UArray 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 recast if unsure.

length :: UArray ty -> CountOf ty #

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

Freeze a MUArray into a UArray by copying all the content is a pristine new buffer

The MUArray in parameter can be still be used after the call without changing the resulting frozen data.

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

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

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

Thaw an immutable array.

The UArray must not be used after thawing.

Creation

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

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

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 #

Arguments

:: forall ty. 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 #

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

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 #

copyToPtr #

Arguments

:: forall ty prim. (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 #

Get a Ptr pointing to the data in the UArray.

Since a UArray is immutable, this Ptr shouldn't be to use to modify the contents

If the UArray is pinned, then its address is returned as is, however if it's unpinned, a pinned copy of the UArray is made before getting the address.

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

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

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

Just like freeze but copy only the first n bytes

The size requested need to be smaller or equal to the length of the MUArray, otherwise a Out of Bounds exception is raised

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

Create a UArray from a Block

The block is still used by the uarray

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

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 #

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 #

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

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

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

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

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

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

equalMemcmp :: PrimType ty => UArray ty -> UArray ty -> Bool #

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

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

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

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

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

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

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

null :: UArray ty -> Bool #

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

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

unsafeTake :: CountOf ty -> UArray ty -> UArray ty #

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

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

unsafeDrop :: CountOf ty -> UArray ty -> UArray ty #

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

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 #

Drop the N elements from the end of the array

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

Take the N elements from the end of the array

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

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

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

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

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

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

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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

isPrefixOf :: PrimType ty => UArray ty -> UArray ty -> Bool #

isSuffixOf :: PrimType ty => UArray ty -> UArray ty -> Bool #

foreignMem #

Arguments

:: PrimType ty 
=> FinalPtr ty

the start pointer with a finalizer

-> CountOf ty

the number of elements (in elements, not bytes)

-> UArray ty 

fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty #

Create a foreign UArray from foreign memory and given offset/size

No check are performed to make sure this is valid, so this is unsafe.

This is particularly useful when dealing with foreign memory and ByteString

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

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

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