primitive-0.8.0.0: Primitive memory-related operations
Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Primitive.Array

Description

Primitive arrays of boxed values.

Synopsis

Documentation

data Array a Source #

Boxed arrays.

Constructors

Array 

Fields

Instances

Instances details
MonadFail Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

fail :: String -> Array a #

MonadFix Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

MonadZip Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

mzip :: Array a -> Array b -> Array (a, b) #

mzipWith :: (a -> b -> c) -> Array a -> Array b -> Array c #

munzip :: Array (a, b) -> (Array a, Array b) #

Foldable Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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 #

toList :: Array a -> [a] #

null :: Array a -> Bool #

length :: Array a -> Int #

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

maximum :: Ord a => Array a -> a #

minimum :: Ord a => Array a -> a #

sum :: Num a => Array a -> a #

product :: Num a => Array a -> a #

Eq1 Array Source #

Since: 0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

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

Ord1 Array Source #

Since: 0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftCompare :: (a -> b -> Ordering) -> Array a -> Array b -> Ordering #

Read1 Array Source #

Since: 0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Array a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Array a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Array a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Array a] #

Show1 Array Source #

Since: 0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Array a] -> ShowS #

Traversable Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) #

sequenceA :: Applicative f => Array (f a) -> f (Array a) #

mapM :: Monad m => (a -> m b) -> Array a -> m (Array b) #

sequence :: Monad m => Array (m a) -> m (Array a) #

Alternative Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

empty :: Array a #

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

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

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

Applicative Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

pure :: a -> Array a #

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

liftA2 :: (a -> b -> c) -> Array a -> Array b -> Array c #

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

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

Functor Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

Monad Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

return :: a -> Array a #

MonadPlus Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

mzero :: Array a #

mplus :: Array a -> Array a -> Array a #

NFData1 Array Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

Lift a => Lift (Array a :: Type) Source # 
Instance details

Defined in Data.Primitive.Array

Methods

lift :: Quote m => Array a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Array a -> Code m (Array a) #

Data a => Data (Array a) Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

Defined in Data.Primitive.Array

Methods

mempty :: Array a #

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

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

Semigroup (Array a) Source #

Since: 0.6.3.0

Instance details

Defined in Data.Primitive.Array

Methods

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

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

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

IsList (Array a) Source # 
Instance details

Defined in Data.Primitive.Array

Associated Types

type Item (Array a) #

Methods

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

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

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

Read a => Read (Array a) Source # 
Instance details

Defined in Data.Primitive.Array

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

Defined in Data.Primitive.Array

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

NFData a => NFData (Array a) Source # 
Instance details

Defined in Data.Primitive.Array

Methods

rnf :: Array a -> () #

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

Defined in Data.Primitive.Array

Methods

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

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

Ord a => Ord (Array a) Source #

Lexicographic ordering. Subject to change between major versions.

Instance details

Defined in Data.Primitive.Array

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 #

type Item (Array a) Source # 
Instance details

Defined in Data.Primitive.Array

type Item (Array a) = a

data MutableArray s a Source #

Mutable boxed arrays associated with a primitive state token.

Constructors

MutableArray 

Fields

Instances

Instances details
(Typeable s, Typeable a) => Data (MutableArray s a) Source # 
Instance details

Defined in Data.Primitive.Array

Methods

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

Defined in Data.Primitive.Array

Methods

(==) :: 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 :: Monad m => Array a -> Int -> m a Source #

Monadically read a value from the immutable array at the given index. 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.

freezeArray Source #

Arguments

:: PrimMonad m 
=> MutableArray (PrimState m) a

source

-> Int

offset

-> Int

length

-> m (Array a) 

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.

thawArray Source #

Arguments

:: PrimMonad m 
=> Array a

source

-> Int

offset

-> Int

length

-> m (MutableArray (PrimState m) a) 

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.

copyArray Source #

Arguments

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

copyMutableArray Source #

Arguments

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

cloneArray Source #

Arguments

:: Array a

source array

-> Int

offset into destination array

-> Int

number of elements to copy

-> Array a 

Return a newly allocated Array with the specified subrange of the provided Array.

Note: The provided array should contain the full subrange specified by the two Ints, but this is not checked.

cloneMutableArray Source #

Arguments

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

fromListN :: IsList l => Int -> [Item l] -> l #

The fromListN function takes the input list's length and potentially uses it to construct the structure l more efficiently compared to fromList. If the given number does not equal to the input list's length the behaviour of fromListN is not specified.

fromListN (length xs) xs == fromList xs

fromList :: IsList l => [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

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.

mapArray' :: (a -> b) -> Array a -> Array b Source #

Strict map over the elements of the array.

traverseArrayP :: PrimMonad m => (a -> m b) -> Array a -> m (Array b) Source #

This is the fastest, most straightforward way to traverse an array, but it only works correctly with a sufficiently "affine" PrimMonad instance. In particular, it must only produce one result array. ListT-transformed monads, for example, will not work right at all.