Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Contiguous (arr :: Type -> Type) where
- type family Element (arr :: Type -> Type) :: Type -> Constraint
- type family Mutable (arr :: Type -> Type) = (r :: Type -> Type -> Type) | r -> arr
- class Always a
- empty :: Contiguous arr => forall a. arr a
- new :: (HasCallStack, Contiguous arr, Element arr b) => Int -> ST s (Mutable arr s b)
- index :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> b
- index# :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> (#b#)
- indexM :: (HasCallStack, Contiguous arr, Element arr b, Monad m) => arr b -> Int -> m b
- read :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> ST s b
- write :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> b -> ST s ()
- resize :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> ST s (Mutable arr s b)
- 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 ()
- copyMutable :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> Mutable arr s b -> Int -> Int -> ST s ()
- clone :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> Int -> arr b
- cloneMutable :: (HasCallStack, Contiguous arr, Element arr b) => Mutable arr s b -> Int -> Int -> ST s (Mutable arr s b)
- 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
- map :: (Contiguous arr, Element arr b, Element arr c) => (b -> c) -> arr b -> arr c
- foldr :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b
- foldl' :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b
- foldr' :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b
- foldMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m
- foldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> a -> m b) -> b -> arr a -> m b
- unsafeFromListN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- unsafeFromListReverseN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
Documentation
class Contiguous (arr :: Type -> Type) where #
A contiguous array of elements.
empty, new, index, index#, indexM, read, write, resize, size, sizeMutable, unsafeFreeze, copy, copyMutable, clone, cloneMutable, equals, unlift, lift
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 #
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.
:: (Contiguous arr, Element arr a) | |
=> Int | length of list |
-> [a] | list |
-> arr a |
unsafeFromListReverseN Source #
:: (Contiguous arr, Element arr a) | |
=> Int | length of list |
-> [a] | list |
-> arr a |