basement-0.0.10: Foundation scrap box of array & string

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

Basement.BoxedArray

Description

Simple boxed array abstraction

Synopsis

Documentation

data Array a #

Array of a

Instances
Functor Array # 
Instance details

Defined in Basement.BoxedArray

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

IsList (Array ty) # 
Instance details

Defined in Basement.BoxedArray

Associated Types

type Item (Array ty) :: Type #

Methods

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

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

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

Eq a => Eq (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

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

Defined in Basement.BoxedArray

Methods

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

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

toConstr :: Array ty -> Constr #

dataTypeOf :: Array ty -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

Show a => Show (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Semigroup (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Monoid (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

NormalForm a => NormalForm (Array a) # 
Instance details

Defined in Basement.BoxedArray

Methods

toNormalForm :: Array a -> () #

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

Defined in Basement.From

Methods

from :: UArray ty -> Array ty #

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

Defined in Basement.From

Methods

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

Defined in Basement.From

Methods

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

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

Defined in Basement.From

Methods

from :: BlockN n ty -> Array ty #

type Item (Array ty) # 
Instance details

Defined in Basement.BoxedArray

type Item (Array ty) = ty

data MArray a st #

Mutable Array of a

length :: Array a -> CountOf a #

mutableLength :: MArray ty st -> Int #

return the numbers of elements in a mutable array

copy :: Array ty -> Array ty #

Copy the element to a new element array

unsafeCopyAtRO #

Arguments

:: PrimMonad prim 
=> MArray ty (PrimState prim)

destination array

-> Offset ty

offset at destination

-> Array 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.

thaw :: PrimMonad prim => Array ty -> prim (MArray 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.

new :: PrimMonad prim => CountOf ty -> prim (MArray ty (PrimState prim)) #

Create a new mutable array of size @n.

all the cells are uninitialized and could contains invalid values.

All mutable arrays are allocated on a 64 bits aligned addresses and always contains a number of bytes multiples of 64 bits.

create #

Arguments

:: CountOf ty

the size of the array

-> (Offset ty -> ty)

the function that set the value at the index

-> Array ty

the array created

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

unsafeFreeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (Array ty) #

Freeze a mutable array into an array.

the MArray must not be changed after freezing.

unsafeThaw :: PrimMonad prim => Array ty -> prim (MArray ty (PrimState prim)) #

Thaw an immutable array.

The Array must not be used after thawing.

freeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (Array ty) #

unsafeWrite :: PrimMonad prim => MArray 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.

unsafeRead :: PrimMonad prim => MArray 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.

unsafeIndex :: Array 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.

write :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> ty -> prim () #

Write to a cell in a mutable array.

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

read :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> prim ty #

read a cell in a mutable array.

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

index :: Array 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.

singleton :: ty -> Array ty #

replicate :: CountOf ty -> ty -> Array ty #

null :: Array ty -> Bool #

take :: CountOf ty -> Array ty -> Array ty #

drop :: CountOf ty -> Array ty -> Array ty #

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

revTake :: CountOf ty -> Array ty -> Array ty #

revDrop :: CountOf ty -> Array ty -> Array ty #

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

splitOn :: (ty -> Bool) -> Array ty -> [Array ty] #

sub :: Array ty -> Offset ty -> Offset ty -> Array ty #

intersperse :: ty -> Array ty -> Array ty #

span :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) #

spanEnd :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) #

break :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) #

breakEnd :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) #

mapFromUnboxed :: PrimType a => (a -> b) -> UArray a -> Array b #

mapToUnboxed :: PrimType b => (a -> b) -> Array a -> UArray b #

cons :: ty -> Array ty -> Array ty #

snoc :: Array ty -> ty -> Array ty #

uncons :: Array ty -> Maybe (ty, Array ty) #

unsnoc :: Array ty -> Maybe (Array ty, ty) #

sortBy :: forall ty. (ty -> ty -> Ordering) -> Array ty -> Array ty #

filter :: forall ty. (ty -> Bool) -> Array ty -> Array ty #

reverse :: Array ty -> Array ty #

elem :: Eq ty => ty -> Array ty -> Bool #

find :: (ty -> Bool) -> Array ty -> Maybe ty #

foldl' :: (a -> ty -> a) -> a -> Array ty -> a #

foldr :: (ty -> a -> a) -> a -> Array ty -> a #

foldl1' :: (ty -> ty -> ty) -> NonEmpty (Array ty) -> ty #

foldr1 :: (ty -> ty -> ty) -> NonEmpty (Array ty) -> ty #

all :: (ty -> Bool) -> Array ty -> Bool #

any :: (ty -> Bool) -> Array ty -> Bool #

isPrefixOf :: Eq ty => Array ty -> Array ty -> Bool #

isSuffixOf :: Eq ty => Array ty -> Array ty -> Bool #

builderAppend :: PrimMonad state => ty -> Builder (Array ty) (MArray ty) ty state err () #

builderBuild :: PrimMonad m => Int -> Builder (Array ty) (MArray ty) ty m err () -> m (Either err (Array ty)) #

builderBuild_ :: PrimMonad m => Int -> Builder (Array ty) (MArray ty) ty m () () -> m (Array ty) #