Copyright | (c) Roman Leshchinskiy 2009-2012 |
---|---|
License | BSD-style |
Maintainer | Roman Leshchinskiy <rl@cse.unsw.edu.au> |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Primitive arrays of boxed values.
Synopsis
- data Array a = Array {}
- data MutableArray s a = MutableArray {
- marray# :: MutableArray# s a
- newArray :: PrimMonad m => Int -> a -> m (MutableArray (PrimState m) a)
- readArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> m a
- writeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> a -> m ()
- indexArray :: Array a -> Int -> a
- indexArrayM :: Applicative m => Array a -> Int -> m a
- indexArray## :: Array a -> Int -> (# a #)
- freezeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> Int -> m (Array a)
- thawArray :: PrimMonad m => Array a -> Int -> Int -> m (MutableArray (PrimState m) a)
- runArray :: (forall s. ST s (MutableArray s a)) -> Array a
- createArray :: Int -> a -> (forall s. MutableArray s a -> ST s ()) -> Array a
- unsafeFreezeArray :: PrimMonad m => MutableArray (PrimState m) a -> m (Array a)
- unsafeThawArray :: PrimMonad m => Array a -> m (MutableArray (PrimState m) a)
- sameMutableArray :: MutableArray s a -> MutableArray s a -> Bool
- copyArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> Array a -> Int -> Int -> m ()
- copyMutableArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> MutableArray (PrimState m) a -> Int -> Int -> m ()
- cloneArray :: Array a -> Int -> Int -> Array a
- cloneMutableArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> Int -> m (MutableArray (PrimState m) a)
- sizeofArray :: Array a -> Int
- sizeofMutableArray :: MutableArray s a -> Int
- emptyArray :: Array a
- arrayFromListN :: Int -> [a] -> Array a
- arrayFromList :: [a] -> Array a
- mapArray' :: (a -> b) -> Array a -> Array b
- traverseArrayP :: PrimMonad m => (a -> m b) -> Array a -> m (Array b)
Documentation
Boxed arrays.
Instances
MonadFail Array Source # | |
Defined in Data.Primitive.Array | |
MonadFix Array Source # | |
Defined in Data.Primitive.Array | |
MonadZip Array Source # | |
Foldable Array Source # | |
Defined in Data.Primitive.Array fold :: Monoid m => Array m -> m # foldMap :: Monoid m => (a -> m) -> Array a -> m # foldMap' :: Monoid m => (a -> m) -> Array a -> m # foldr :: (a -> b -> b) -> b -> Array a -> b # foldr' :: (a -> b -> b) -> b -> Array a -> b # foldl :: (b -> a -> b) -> b -> Array a -> b # foldl' :: (b -> a -> b) -> b -> Array a -> b # foldr1 :: (a -> a -> a) -> Array a -> a # foldl1 :: (a -> a -> a) -> Array a -> a # elem :: Eq a => a -> Array a -> Bool # maximum :: Ord a => Array a -> a # minimum :: Ord a => Array a -> a # | |
Eq1 Array Source # | Since: 0.6.4.0 |
Ord1 Array Source # | Since: 0.6.4.0 |
Defined in Data.Primitive.Array | |
Read1 Array Source # | Since: 0.6.4.0 |
Defined in Data.Primitive.Array | |
Show1 Array Source # | Since: 0.6.4.0 |
Traversable Array Source # | |
Alternative Array Source # | |
Applicative Array Source # | |
Functor Array Source # | |
Monad Array Source # | |
MonadPlus Array Source # | |
NFData1 Array Source # | |
Defined in Data.Primitive.Array | |
Lift a => Lift (Array a :: Type) Source # | |
Data a => Data (Array a) Source # | |
Defined in Data.Primitive.Array gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array a -> c (Array a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a) # toConstr :: Array a -> Constr # dataTypeOf :: Array a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a)) # gmapT :: (forall b. Data b => b -> b) -> Array a -> Array a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # | |
Monoid (Array a) Source # | |
Semigroup (Array a) Source # | Since: 0.6.3.0 |
IsList (Array a) Source # | |
Read a => Read (Array a) Source # | |
Show a => Show (Array a) Source # | |
NFData a => NFData (Array a) Source # | |
Defined in Data.Primitive.Array | |
Eq a => Eq (Array a) Source # | |
Ord a => Ord (Array a) Source # | Lexicographic ordering. Subject to change between major versions. |
type Item (Array a) Source # | |
Defined in Data.Primitive.Array |
data MutableArray s a Source #
Mutable boxed arrays associated with a primitive state token.
MutableArray | |
|
Instances
(Typeable s, Typeable a) => Data (MutableArray s a) Source # | |
Defined in Data.Primitive.Array gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableArray s a -> c (MutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableArray s a) # toConstr :: MutableArray s a -> Constr # dataTypeOf :: MutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> MutableArray s a -> MutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> MutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # | |
Eq (MutableArray s a) Source # | |
Defined in Data.Primitive.Array (==) :: MutableArray s a -> MutableArray s a -> Bool # (/=) :: MutableArray s a -> MutableArray s a -> Bool # |
newArray :: PrimMonad m => Int -> a -> m (MutableArray (PrimState m) a) Source #
Create a new mutable array of the specified size and initialise all elements with the given value.
Note: this function does not check if the input is non-negative.
readArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> m a Source #
Read a value from the array at the given index.
Note: this function does not do bounds checking.
writeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> a -> m () Source #
Write a value to the array at the given index.
Note: this function does not do bounds checking.
indexArray :: Array a -> Int -> a Source #
Read a value from the immutable array at the given index.
Note: this function does not do bounds checking.
indexArrayM :: Applicative m => Array a -> Int -> m a Source #
Read a value from the immutable array at the given index using an applicative. This allows us to be strict in the array while remaining lazy in the read element which is very useful for collective operations. Suppose we want to copy an array. We could do something like this:
copy marr arr ... = do ... writeArray marr i (indexArray arr i) ... ...
But since the arrays are lazy, the calls to indexArray
will not be
evaluated. Rather, marr
will be filled with thunks each of which would
retain a reference to arr
. This is definitely not what we want!
With indexArrayM
, we can instead write
copy marr arr ... = do ... x <- indexArrayM arr i writeArray marr i x ...
Now, indexing is executed immediately although the returned element is still not evaluated.
Note: this function does not do bounds checking.
indexArray## :: Array 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.
Create an immutable copy of a slice of an array.
This operation makes a copy of the specified section, so it is safe to continue using the mutable array afterward.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
Create a mutable array from a slice of an immutable array.
This operation makes a copy of the specified slice, so it is safe to use the immutable array afterward.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
runArray :: (forall s. ST s (MutableArray s a)) -> Array a Source #
Execute the monadic action and freeze the resulting array.
runArray m = runST $ m >>= unsafeFreezeArray
createArray :: Int -> a -> (forall s. MutableArray s a -> ST s ()) -> Array 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 emptyArray
(rather than a new copy thereof).
createArray 0 _ _ = emptyArray createArray n x f = runArray $ do mary <- newArray n x f mary pure mary
unsafeFreezeArray :: PrimMonad m => MutableArray (PrimState m) a -> m (Array a) Source #
Convert a mutable array to an immutable one without copying. The array should not be modified after the conversion.
unsafeThawArray :: PrimMonad m => Array a -> m (MutableArray (PrimState m) a) Source #
Convert an immutable array to an mutable one without copying. The immutable array should not be used after the conversion.
sameMutableArray :: MutableArray s a -> MutableArray s a -> Bool Source #
Check whether the two arrays refer to the same memory block.
:: PrimMonad m | |
=> MutableArray (PrimState m) a | destination array |
-> Int | offset into destination array |
-> Array a | source array |
-> Int | offset into source array |
-> Int | number of elements to copy |
-> m () |
Copy a slice of an immutable array to a mutable array.
Note: this function does not do bounds or overlap checking.
:: PrimMonad m | |
=> MutableArray (PrimState m) a | destination array |
-> Int | offset into destination array |
-> MutableArray (PrimState m) a | source array |
-> Int | offset into source array |
-> Int | number of elements to copy |
-> m () |
Copy a slice of a mutable array to another array. The two arrays may overlap.
Note: this function does not do bounds or overlap checking.
:: PrimMonad m | |
=> MutableArray (PrimState m) a | source array |
-> Int | offset into destination array |
-> Int | number of elements to copy |
-> m (MutableArray (PrimState m) a) |
Return a newly allocated MutableArray
. with the specified subrange of
the provided MutableArray
. The provided MutableArray
should contain the
full subrange specified by the two Ints, but this is not checked.
Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.
sizeofArray :: Array a -> Int Source #
The number of elements in an immutable array.
sizeofMutableArray :: MutableArray s a -> Int Source #
The number of elements in a mutable array.
emptyArray :: Array a Source #
The empty Array
.
arrayFromListN :: Int -> [a] -> Array a Source #
Create an array from a list of a known length. If the length of the list does not match the given length, this throws an exception.
arrayFromList :: [a] -> Array a Source #
Create an array from a list.