Copyright | (c) 2015 Dan Doel |
---|---|
License | BSD3 |
Maintainer | libraries@haskell.org |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Small arrays are boxed (im)mutable arrays.
The underlying structure of the Array
type contains a card table, allowing
segments of the array to be marked as having been mutated. This allows the
garbage collector to only re-traverse segments of the array that have been
marked during certain phases, rather than having to traverse the entire
array.
SmallArray
lacks this table. This means that it takes up less memory and
has slightly faster writes. It is also more efficient during garbage
collection so long as the card table would have a single entry covering the
entire array. These advantages make them suitable for use as arrays that are
known to be small.
The card size is 128, so for uses much larger than that,
Array
would likely be superior.
Synopsis
- data SmallArray a = SmallArray (SmallArray# a)
- data SmallMutableArray s a = SmallMutableArray (SmallMutableArray# s a)
- newSmallArray :: PrimMonad m => Int -> a -> m (SmallMutableArray (PrimState m) a)
- readSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m a
- writeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> a -> m ()
- copySmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> SmallArray a -> Int -> Int -> m ()
- copySmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> SmallMutableArray (PrimState m) a -> Int -> Int -> m ()
- indexSmallArray :: SmallArray a -> Int -> a
- indexSmallArrayM :: Monad m => SmallArray a -> Int -> m a
- indexSmallArray## :: SmallArray a -> Int -> (# a #)
- cloneSmallArray :: SmallArray a -> Int -> Int -> SmallArray a
- cloneSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> Int -> m (SmallMutableArray (PrimState m) a)
- freezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> Int -> m (SmallArray a)
- unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a)
- thawSmallArray :: PrimMonad m => SmallArray a -> Int -> Int -> m (SmallMutableArray (PrimState m) a)
- unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a)
- runSmallArray :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray a
- createSmallArray :: Int -> a -> (forall s. SmallMutableArray s a -> ST s ()) -> SmallArray a
- sizeofSmallArray :: SmallArray a -> Int
- sizeofSmallMutableArray :: SmallMutableArray s a -> Int
- shrinkSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m ()
- emptySmallArray :: SmallArray a
- smallArrayFromList :: [a] -> SmallArray a
- smallArrayFromListN :: Int -> [a] -> SmallArray a
- mapSmallArray' :: (a -> b) -> SmallArray a -> SmallArray b
- traverseSmallArrayP :: PrimMonad m => (a -> m b) -> SmallArray a -> m (SmallArray b)
Documentation
data SmallArray a Source #
Instances
data SmallMutableArray s a Source #
Instances
Eq (SmallMutableArray s a) Source # | |
Defined in Data.Primitive.SmallArray (==) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # (/=) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # | |
(Typeable s, Typeable a) => Data (SmallMutableArray s a) Source # | |
Defined in Data.Primitive.SmallArray gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallMutableArray s a -> c (SmallMutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallMutableArray s a) # toConstr :: SmallMutableArray s a -> Constr # dataTypeOf :: SmallMutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallMutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallMutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> SmallMutableArray s a -> SmallMutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallMutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallMutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # |
:: PrimMonad m | |
=> Int | size |
-> a | initial contents |
-> m (SmallMutableArray (PrimState m) a) |
Create a new small mutable array.
Note: this function does not check if the input is non-negative.
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | array |
-> Int | index |
-> m a |
Read the element at a given index in a mutable array.
Note: this function does not do bounds checking.
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | array |
-> Int | index |
-> a | new element |
-> m () |
Write an element at the given idex in a mutable array.
Note: this function does not do bounds checking.
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | destination |
-> Int | destination offset |
-> SmallArray a | source |
-> Int | source offset |
-> Int | length |
-> m () |
Copy a slice of an immutable array into a mutable array.
Note: this function does not do bounds or overlap checking.
copySmallMutableArray Source #
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | destination |
-> Int | destination offset |
-> SmallMutableArray (PrimState m) a | source |
-> Int | source offset |
-> Int | length |
-> m () |
Copy a slice of one mutable array into another.
Note: this function does not do bounds or overlap checking.
:: SmallArray a | array |
-> Int | index |
-> a |
Look up an element in an immutable array.
Note: this function does not do bounds checking.
:: Monad m | |
=> SmallArray a | array |
-> Int | index |
-> m a |
Look up an element in an immutable array.
The purpose of returning a result using a monad is to allow the caller to avoid retaining references to the array. Evaluating the return value will cause the array lookup to be performed, even though it may not require the element of the array to be evaluated (which could throw an exception). For instance:
data Box a = Box a ... f sa = case indexSmallArrayM sa 0 of Box x -> ...
x
is not a closure that references sa
as it would be if we instead
wrote:
let x = indexSmallArray sa 0
It also does not prevent sa
from being garbage collected.
Note that Identity
is not adequate for this use, as it is a newtype, and
cannot be evaluated without evaluating the element.
Note: this function does not do bounds checking.
indexSmallArray## :: SmallArray a -> Int -> (# a #) Source #
Read a value from the immutable array at the given index, returning the result in an unboxed unary tuple. This is currently used to implement folds.
Note: this function does not do bounds checking.
:: SmallArray a | source |
-> Int | offset |
-> Int | length |
-> SmallArray a |
Create a copy of a slice of an immutable array.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
cloneSmallMutableArray Source #
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | source |
-> Int | offset |
-> Int | length |
-> m (SmallMutableArray (PrimState m) a) |
Create a copy of a slice of a mutable array.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
:: PrimMonad m | |
=> SmallMutableArray (PrimState m) a | source |
-> Int | offset |
-> Int | length |
-> m (SmallArray a) |
Create an immutable array corresponding to a slice of a mutable array.
This operation copies the portion of the array to be frozen.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a) Source #
Render a mutable array immutable.
This operation performs no copying, so care must be taken not to modify the input array after freezing.
:: PrimMonad m | |
=> SmallArray a | source |
-> Int | offset |
-> Int | length |
-> m (SmallMutableArray (PrimState m) a) |
Create a mutable array corresponding to a slice of an immutable array.
This operation copies the portion of the array to be thawed.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a) Source #
Render an immutable array mutable.
This operation performs no copying, so care must be taken with its use.
runSmallArray :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray a Source #
Execute the monadic action and freeze the resulting array.
runSmallArray m = runST $ m >>= unsafeFreezeSmallArray
createSmallArray :: Int -> a -> (forall s. SmallMutableArray s a -> ST s ()) -> SmallArray a Source #
Create an array of the given size with a default value,
apply the monadic function and freeze the result. If the
size is 0, return emptySmallArray
(rather than a new copy thereof).
createSmallArray 0 _ _ = emptySmallArray createSmallArray n x f = runSmallArray $ do mary <- newSmallArray n x f mary pure mary
sizeofSmallArray :: SmallArray a -> Int Source #
The number of elements in an immutable array.
sizeofSmallMutableArray :: SmallMutableArray s a -> Int Source #
The number of elements in a mutable array.
shrinkSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m () Source #
Shrink the mutable array in place. The size given must be equal to or less than the current size of the array. This is not checked.
emptySmallArray :: SmallArray a Source #
The empty SmallArray
.
smallArrayFromList :: [a] -> SmallArray a Source #
Create a SmallArray
from a list.
smallArrayFromListN :: Int -> [a] -> SmallArray a Source #
Create a SmallArray
from a list of a known length. If the length
of the list does not match the given length, this throws an exception.
mapSmallArray' :: (a -> b) -> SmallArray a -> SmallArray b Source #
Strict map over the elements of the array.
traverseSmallArrayP :: PrimMonad m => (a -> m b) -> SmallArray a -> m (SmallArray b) Source #