Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Contiguous (arr :: Type -> Type) where
- type Mutable arr = (r :: Type -> Type -> Type) | r -> arr
- type Element arr :: Type -> Constraint
- empty :: arr a
- null :: arr b -> Bool
- new :: (PrimMonad m, Element arr b) => Int -> m (Mutable arr (PrimState m) b)
- replicateM :: (PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b)
- index :: Element arr b => arr b -> Int -> b
- index# :: Element arr b => arr b -> Int -> (#b#)
- indexM :: (Element arr b, Monad m) => arr b -> Int -> m b
- read :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m b
- write :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> b -> m ()
- resize :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b)
- size :: Element arr b => arr b -> Int
- sizeMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int
- unsafeFreeze :: PrimMonad m => Mutable arr (PrimState m) b -> m (arr b)
- thaw :: (PrimMonad m, Element arr b) => arr b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- copy :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> arr b -> Int -> Int -> m ()
- copyMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Mutable arr (PrimState m) b -> Int -> Int -> m ()
- clone :: Element arr b => arr b -> Int -> Int -> arr b
- cloneMutable :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- equals :: (Element arr b, Eq b) => arr b -> arr b -> Bool
- unlift :: arr b -> ArrayArray#
- lift :: ArrayArray# -> arr b
- sameMutable :: Mutable arr s a -> Mutable arr s a -> Bool
- singleton :: Element arr a => a -> arr a
- doubleton :: Element arr a => a -> a -> arr a
- tripleton :: Element arr a => a -> a -> a -> arr a
- rnf :: (NFData a, Element arr a) => arr a -> ()
- class Always a
- append :: (Contiguous arr, Element arr a) => arr a -> arr a -> arr a
- map :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c
- map' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c
- imap :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c
- mapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (a -> a) -> Mutable arr (PrimState m) a -> m ()
- imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m ()
- 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
- 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
- traverse :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f (arr b)
- traverseP :: (PrimMonad m, Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b)
- traverse_ :: (Contiguous arr, Element arr a, Applicative f) => (a -> f b) -> arr a -> f ()
- itraverse_ :: (Contiguous arr, Element arr a, Applicative f) => (Int -> a -> f b) -> arr a -> f ()
- unsafeFromListN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- unsafeFromListReverseN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- liftHashWithSalt :: (Contiguous arr, Element arr a) => (Int -> a -> Int) -> Int -> arr a -> Int
- same :: Contiguous arr => arr a -> arr a -> Bool
Documentation
class Contiguous (arr :: Type -> Type) where Source #
A contiguous array of elements.
type Mutable arr = (r :: Type -> Type -> Type) | r -> arr Source #
type Element arr :: Type -> Constraint 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 #
thaw :: (PrimMonad m, Element arr b) => arr b -> Int -> Int -> m (Mutable arr (PrimState m) 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 #
singleton :: Element arr a => a -> arr a Source #
doubleton :: Element arr a => a -> a -> arr a Source #
Instances
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 # | |
Defined in Data.Primitive.Contiguous |
append :: (Contiguous arr, Element arr a) => arr a -> arr a -> arr a Source #
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.
map' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c Source #
Map strictly over the elements of an array.
imap :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c Source #
Map over the elements of an array with the index.
mapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Strictly map over a mutable array, modifying the elements in place.
imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Strictly map over a mutable array with indices, modifying the elements in place.
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, Element arr b, Applicative f) => (a -> f b) -> arr a -> f (arr b) Source #
traverseP :: (PrimMonad m, Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b) Source #
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 #
:: (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.