contiguous-0.2.0.0: Unified interface for primitive arrays

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Contiguous

Synopsis

Documentation

class Contiguous (arr :: Type -> Type) where Source #

A contiguous array of elements.

Associated Types

type Mutable arr = (r :: Type -> Type -> Type) | r -> arr Source #

type Element arr :: Type -> Constraint Source #

Methods

empty :: arr a Source #

new :: Element arr b => Int -> ST s (Mutable arr s b) Source #

index :: Element arr b => arr b -> Int -> b Source #

index# :: Element arr b => arr b -> Int -> (#b#) Source #

indexM :: (Element arr b, Monad m) => arr b -> Int -> m b Source #

read :: Element arr b => Mutable arr s b -> Int -> ST s b Source #

write :: Element arr b => Mutable arr s b -> Int -> b -> ST s () Source #

resize :: Element arr b => Mutable arr s b -> Int -> ST s (Mutable arr s b) Source #

size :: Element arr b => arr b -> Int Source #

sizeMutable :: Element arr b => Mutable arr s b -> ST s Int Source #

unsafeFreeze :: Mutable arr s b -> ST s (arr b) Source #

copy :: Element arr b => Mutable arr s b -> Int -> arr b -> Int -> Int -> ST s () Source #

copyMutable :: Element arr b => Mutable arr s b -> Int -> Mutable arr s b -> Int -> Int -> ST s () Source #

clone :: Element arr b => arr b -> Int -> Int -> arr b Source #

cloneMutable :: Element arr b => Mutable arr s b -> Int -> Int -> ST s (Mutable arr s b) Source #

equals :: (Element arr b, Eq b) => arr b -> arr b -> Bool Source #

unlift :: arr b -> ArrayArray# Source #

lift :: ArrayArray# -> arr b Source #

Instances

Contiguous UnliftedArray Source # 

Associated Types

type Mutable (UnliftedArray :: Type -> Type) = (r :: Type -> Type -> Type) Source #

type Element (UnliftedArray :: Type -> Type) :: Type -> Constraint Source #

Methods

empty :: UnliftedArray a Source #

new :: Element UnliftedArray b => Int -> ST s (Mutable UnliftedArray s b) Source #

index :: Element UnliftedArray b => UnliftedArray b -> Int -> b Source #

index# :: Element UnliftedArray b => UnliftedArray b -> Int -> (#LiftedRep, b#) Source #

indexM :: (Element UnliftedArray b, Monad m) => UnliftedArray b -> Int -> m b Source #

read :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> ST s b Source #

write :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> b -> ST s () Source #

resize :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> ST s (Mutable UnliftedArray s b) Source #

size :: Element UnliftedArray b => UnliftedArray b -> Int Source #

sizeMutable :: Element UnliftedArray b => Mutable UnliftedArray s b -> ST s Int Source #

unsafeFreeze :: Mutable UnliftedArray s b -> ST s (UnliftedArray b) Source #

copy :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> UnliftedArray b -> Int -> Int -> ST s () Source #

copyMutable :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> Mutable UnliftedArray s b -> Int -> Int -> ST s () Source #

clone :: Element UnliftedArray b => UnliftedArray b -> Int -> Int -> UnliftedArray b Source #

cloneMutable :: Element UnliftedArray b => Mutable UnliftedArray s b -> Int -> Int -> ST s (Mutable UnliftedArray s b) Source #

equals :: (Element UnliftedArray b, Eq b) => UnliftedArray b -> UnliftedArray b -> Bool Source #

unlift :: UnliftedArray b -> ArrayArray# Source #

lift :: ArrayArray# -> UnliftedArray b Source #

Contiguous PrimArray Source # 

Associated Types

type Mutable (PrimArray :: Type -> Type) = (r :: Type -> Type -> Type) Source #

type Element (PrimArray :: Type -> Type) :: Type -> Constraint Source #

Contiguous Array Source # 

Associated Types

type Mutable (Array :: Type -> Type) = (r :: Type -> Type -> Type) Source #

type Element (Array :: Type -> Type) :: Type -> Constraint Source #

Methods

empty :: Array a Source #

new :: Element Array b => Int -> ST s (Mutable Array s b) Source #

index :: Element Array b => Array b -> Int -> b Source #

index# :: Element Array b => Array b -> Int -> (#LiftedRep, b#) Source #

indexM :: (Element Array b, Monad m) => Array b -> Int -> m b Source #

read :: Element Array b => Mutable Array s b -> Int -> ST s b Source #

write :: Element Array b => Mutable Array s b -> Int -> b -> ST s () Source #

resize :: Element Array b => Mutable Array s b -> Int -> ST s (Mutable Array s b) Source #

size :: Element Array b => Array b -> Int Source #

sizeMutable :: Element Array b => Mutable Array s b -> ST s Int Source #

unsafeFreeze :: Mutable Array s b -> ST s (Array b) Source #

copy :: Element Array b => Mutable Array s b -> Int -> Array b -> Int -> Int -> ST s () Source #

copyMutable :: Element Array b => Mutable Array s b -> Int -> Mutable Array s b -> Int -> Int -> ST s () Source #

clone :: Element Array b => Array b -> Int -> Int -> Array b Source #

cloneMutable :: Element Array b => Mutable Array s b -> Int -> Int -> ST s (Mutable Array s b) Source #

equals :: (Element Array b, Eq b) => Array b -> Array b -> Bool Source #

unlift :: Array b -> ArrayArray# Source #

lift :: ArrayArray# -> Array b Source #

class Always a Source #

Instances

map :: (Contiguous arr, Element arr b, Element arr c) => (b -> c) -> arr b -> arr c Source #

Map over the elements of an array.

foldr :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b Source #

Right fold over the element of an array.

foldl' :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b Source #

Strict left fold over the elements of an array.

foldr' :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b Source #

Strict right fold over the elements of an array.

foldMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m Source #

Strict monoidal fold over the elements of an array.

foldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> a -> m b) -> b -> arr a -> m b Source #

Strict left monadic fold over the elements of an array.

unsafeFromListN Source #

Arguments

:: (Contiguous arr, Element arr a) 
=> Int

length of list

-> [a]

list

-> arr a 

Create an array from a list. If the given length does not match the actual length, this function has undefined behavior.

unsafeFromListReverseN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a Source #

Create an array from a list, reversing the order of the elements. If the given length does not match the actual length, this function has undefined behavior.