Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Contiguous (arr :: Type -> Type)
- 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 => arr a
- null :: Contiguous arr => arr b -> Bool
- replicateM :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b)
- rnf :: (Contiguous arr, NFData a, Element arr a) => arr a -> ()
- new :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Int -> m (Mutable arr (PrimState m) 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, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> m b
- write :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> b -> m ()
- resize :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b)
- size :: (Contiguous arr, Element arr b) => arr b -> Int
- sizeMutable :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int
- unsafeFreeze :: (Contiguous arr, PrimMonad m) => Mutable arr (PrimState m) b -> m (arr b)
- copy :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> arr b -> Int -> Int -> m ()
- copyMutable :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> Mutable arr (PrimState m) b -> Int -> Int -> m ()
- clone :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> Int -> arr b
- cloneMutable :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- thaw :: (HasCallStack, Contiguous arr, PrimMonad m, Element arr b) => arr b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- equals :: (Contiguous arr, Element arr b, Eq b) => arr b -> arr b -> Bool
- unlift :: Contiguous arr => arr b -> ArrayArray#
- lift :: Contiguous arr => ArrayArray# -> arr b
- singleton :: (Contiguous arr, Element arr a) => a -> arr a
- doubleton :: (Contiguous arr, Element arr a) => a -> a -> arr a
- tripleton :: (Contiguous arr, Element arr a) => a -> a -> a -> arr 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
- 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
- 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)
- 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 ()
- imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m ()
- traverseP :: (PrimMonad m, Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b)
- 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) #
A contiguous array of elements.
empty, null, new, replicateM, index, index#, indexM, read, write, resize, size, sizeMutable, unsafeFreeze, thaw, copy, copyMutable, clone, cloneMutable, equals, unlift, lift, sameMutable, singleton, doubleton, tripleton, rnf
Instances
type family Element (arr :: Type -> Type) :: Type -> Constraint #
Instances
type Element Array | |
Defined in Data.Primitive.Contiguous | |
type Element UnliftedArray | |
Defined in Data.Primitive.Contiguous | |
type Element PrimArray | |
Defined in Data.Primitive.Contiguous |
type family Mutable (arr :: Type -> Type) = (r :: Type -> Type -> Type) | r -> arr #
Instances
type Mutable Array | |
Defined in Data.Primitive.Contiguous | |
type Mutable UnliftedArray | |
Defined in Data.Primitive.Contiguous | |
type Mutable PrimArray | |
Defined in Data.Primitive.Contiguous |
A typeclass that is satisfied by all types. This is used
used to provide a fake constraint for Array
and SmallArray
.
Instances
Always a | |
Defined in Data.Primitive.Contiguous |
Primitives
empty :: Contiguous arr => arr a #
null :: Contiguous arr => arr b -> Bool #
replicateM :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b) #
rnf :: (Contiguous arr, NFData a, Element arr a) => arr a -> () #
new :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Int -> m (Mutable arr (PrimState m) 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, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> m b Source #
write :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> b -> m () Source #
resize :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b) Source #
size :: (Contiguous arr, Element arr b) => arr b -> Int #
sizeMutable :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int #
unsafeFreeze :: (Contiguous arr, PrimMonad m) => Mutable arr (PrimState m) b -> m (arr b) #
copy :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> arr b -> Int -> Int -> m () Source #
copyMutable :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> Mutable arr (PrimState m) b -> Int -> Int -> m () Source #
clone :: (HasCallStack, Contiguous arr, Element arr b) => arr b -> Int -> Int -> arr b Source #
cloneMutable :: (HasCallStack, Contiguous arr, Element arr b, PrimMonad m) => Mutable arr (PrimState m) b -> Int -> Int -> m (Mutable arr (PrimState m) b) Source #
thaw :: (HasCallStack, Contiguous arr, PrimMonad m, Element arr b) => arr b -> Int -> Int -> m (Mutable arr (PrimState m) b) Source #
unlift :: Contiguous arr => arr b -> ArrayArray# #
lift :: Contiguous arr => ArrayArray# -> arr b #
Synthetic Functions
singleton :: (Contiguous arr, Element arr a) => a -> arr a #
doubleton :: (Contiguous arr, Element arr a) => a -> a -> arr a #
tripleton :: (Contiguous arr, Element arr a) => a -> a -> a -> arr 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 over the elements of an array.
map' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c #
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 #
Map over the elements of an array with the index.
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 #
Monoidal fold over the element 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.
traverse :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f (arr 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 () #
imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m () #
Strictly map over a mutable array with indices, modifying the elements in place.
traverseP :: (PrimMonad m, Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b) #
:: (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 |
liftHashWithSalt :: (Contiguous arr, Element arr a) => (Int -> a -> Int) -> Int -> arr a -> Int #
same :: Contiguous arr => arr a -> arr a -> Bool #
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.