primitive-0.6.2.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Array

Description

Primitive arrays of boxed values.

Synopsis

Documentation

data Array a #

Boxed arrays

Constructors

Array 

Fields

Instances

Monad Array # 

Methods

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

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

return :: a -> Array a #

fail :: String -> Array a #

Functor Array # 

Methods

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

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

MonadFix Array # 

Methods

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

Applicative Array # 

Methods

pure :: a -> Array a #

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

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

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

Foldable Array # 

Methods

fold :: Monoid m => Array m -> 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 #

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

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

Alternative Array # 

Methods

empty :: Array a #

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

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

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

MonadPlus Array # 

Methods

mzero :: Array a #

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

IsList (Array a) # 

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

Eq a => Eq (Array a) # 

Methods

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

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

Data a => Data (Array a) # 

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

Ord a => Ord (Array a) # 

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 #

Read a => Read (Array a) # 
Show a => Show (Array a) # 

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Monoid (Array a) # 

Methods

mempty :: Array a #

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

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

PrimUnlifted (Array a) # 
type Item (Array a) # 
type Item (Array a) = a

data MutableArray s a #

Mutable boxed arrays associated with a primitive state token.

Constructors

MutableArray 

Fields

Instances

Eq (MutableArray s a) # 

Methods

(==) :: MutableArray s a -> MutableArray s a -> Bool #

(/=) :: MutableArray s a -> MutableArray s a -> Bool #

(Typeable * s, Typeable * a) => Data (MutableArray s a) # 

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

PrimUnlifted (MutableArray s a) # 

newArray :: PrimMonad m => Int -> a -> m (MutableArray (PrimState m) a) #

Create a new mutable array of the specified size and initialise all elements with the given value.

readArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> m a #

Read a value from the array at the given index.

writeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> a -> m () #

Write a value to the array at the given index.

indexArray :: Array a -> Int -> a #

Read a value from the immutable array at the given index.

indexArrayM :: Monad m => Array a -> Int -> m a #

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

freezeArray #

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.

thawArray #

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.

unsafeFreezeArray :: PrimMonad m => MutableArray (PrimState m) a -> m (Array a) #

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

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 #

Check whether the two arrays refer to the same memory block.

copyArray #

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.

copyMutableArray #

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 not be the same.

cloneArray #

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. The provided Array should contain the full subrange specified by the two Ints, but this is not checked.

cloneMutableArray #

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.

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

The fromListN function takes the input list's length as a hint. Its behaviour should be equivalent to fromList. The hint can be used to construct the structure l more efficiently compared to fromList. If the given hint does not equal to the input list's length the behaviour of fromListN is not specified.

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

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