contiguous-checked-0.2.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Contiguous

Contents

Synopsis

Documentation

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

A contiguous array of elements.

Associated Types

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

type Element (arr :: Type -> Type) :: Type -> Constraint #

Methods

empty :: arr a #

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

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

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

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

unlift :: arr b -> ArrayArray# #

lift :: ArrayArray# -> arr b #

Instances

Contiguous UnliftedArray 

Associated Types

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

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

Contiguous PrimArray 
Contiguous Array 

Associated Types

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

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

Methods

empty :: Array a #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

unlift :: Array b -> ArrayArray# #

lift :: ArrayArray# -> Array b #

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

class Always a #

Instances

Always a 

Primitives

empty :: Contiguous arr => forall a. arr a #

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

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

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

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

read :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> ST s b Source #

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

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

size :: Contiguous arr => forall b. Element arr b => arr b -> Int #

sizeMutable :: Contiguous arr => forall b s. Element arr b => Mutable arr s b -> ST s Int #

unsafeFreeze :: Contiguous arr => forall s b. Mutable arr s b -> ST s (arr b) #

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

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

clone :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> Int -> arr b Source #

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

equals :: Contiguous arr => forall b. (Element arr b, Eq b) => arr b -> arr b -> Bool #

unlift :: Contiguous arr => forall b. arr b -> ArrayArray# #

lift :: Contiguous arr => forall b. ArrayArray# -> arr b #

Synthetic Functions

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

Map over the elements of an array.

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

Right fold over the element of an array.

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

Strict left fold over the elements of an array.

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

Strict right fold over the elements of an array.

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

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 #

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 

unsafeFromListReverseN Source #

Arguments

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

length of list

-> [a]

list

-> arr a