contiguous-0.3.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 #

null :: arr b -> Bool Source #

new :: (PrimMonad m, Element arr b) => Int -> m (Mutable arr (PrimState m) b) Source #

replicateM :: (PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) 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 :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b) Source #

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

sizeMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable arr (PrimState m) b -> m (arr b) Source #

copy :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> arr b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Mutable arr (PrimState m) b -> Int -> Int -> m () Source #

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

cloneMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Int -> m (Mutable arr (PrimState m) b) Source #

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

unlift :: arr b -> ArrayArray# Source #

lift :: ArrayArray# -> arr b Source #

sameMutable :: Mutable arr s a -> Mutable arr s a -> Bool Source #

rnf :: (NFData a, Element arr a) => arr a -> () Source #

Instances
Contiguous UnliftedArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

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

type Element UnliftedArray :: Type -> Constraint Source #

Methods

empty :: UnliftedArray a Source #

null :: UnliftedArray b -> Bool Source #

new :: (PrimMonad m, Element UnliftedArray b) => Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

replicateM :: (PrimMonad m, Element UnliftedArray b) => Int -> b -> m (Mutable UnliftedArray (PrimState m) b) Source #

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

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

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

read :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

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

sizeMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable UnliftedArray (PrimState m) b -> m (UnliftedArray b) Source #

copy :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> UnliftedArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m () Source #

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

cloneMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

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

unlift :: UnliftedArray b -> ArrayArray# Source #

lift :: ArrayArray# -> UnliftedArray b Source #

sameMutable :: Mutable UnliftedArray s a -> Mutable UnliftedArray s a -> Bool Source #

rnf :: (NFData a, Element UnliftedArray a) => UnliftedArray a -> () Source #

Contiguous PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

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

type Element PrimArray :: Type -> Constraint Source #

Methods

empty :: PrimArray a Source #

null :: PrimArray b -> Bool Source #

new :: (PrimMonad m, Element PrimArray b) => Int -> m (Mutable PrimArray (PrimState m) b) Source #

replicateM :: (PrimMonad m, Element PrimArray b) => Int -> b -> m (Mutable PrimArray (PrimState m) b) Source #

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

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

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

read :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

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

sizeMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable PrimArray (PrimState m) b -> m (PrimArray b) Source #

copy :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> PrimArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Mutable PrimArray (PrimState m) b -> Int -> Int -> m () Source #

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

cloneMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

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

unlift :: PrimArray b -> ArrayArray# Source #

lift :: ArrayArray# -> PrimArray b Source #

sameMutable :: Mutable PrimArray s a -> Mutable PrimArray s a -> Bool Source #

rnf :: (NFData a, Element PrimArray a) => PrimArray a -> () Source #

Contiguous Array Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

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

type Element Array :: Type -> Constraint Source #

Methods

empty :: Array a Source #

null :: Array b -> Bool Source #

new :: (PrimMonad m, Element Array b) => Int -> m (Mutable Array (PrimState m) b) Source #

replicateM :: (PrimMonad m, Element Array b) => Int -> b -> m (Mutable Array (PrimState m) b) Source #

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

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

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

read :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m (Mutable Array (PrimState m) b) Source #

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

sizeMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable Array (PrimState m) b -> m (Array b) Source #

copy :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Array b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Mutable Array (PrimState m) b -> Int -> Int -> m () Source #

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

cloneMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Int -> m (Mutable Array (PrimState m) b) Source #

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

unlift :: Array b -> ArrayArray# Source #

lift :: ArrayArray# -> Array b Source #

sameMutable :: Mutable Array s a -> Mutable Array s a -> Bool Source #

rnf :: (NFData a, Element Array a) => Array a -> () Source #

class Always a Source #

A typeclass that is satisfied by all types. This is used used to provide a fake constraint for Array and SmallArray.

Instances
Always a Source # 
Instance details

Defined in Data.Primitive.Contiguous

map :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 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.

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

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

traverse_ :: (Contiguous arr, Element arr a, Applicative f) => (a -> f b) -> arr a -> f () Source #

itraverse_ :: (Contiguous arr, Element arr a, Applicative f) => (Int -> a -> f b) -> arr a -> f () Source #

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.

liftHashWithSalt :: (Contiguous arr, Element arr a) => (Int -> a -> Int) -> Int -> arr a -> Int Source #

same :: Contiguous arr => arr a -> arr a -> Bool Source #

This function does not behave deterministically. Optimization level and inlining can affect its results. However, the one thing that can be counted on is that if it returns True, the two immutable arrays are definitely the same. This is useful as shortcut for equality tests. However, keep in mind that a result of False tells us nothing about the arguments.