primitive-unlifted-2.1.0.0: Primitive GHC types with unlifted types inside
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Primitive.Unlifted.Array

Description

GHC contains three general classes of value types:

  1. Unboxed types: values are machine values made up of fixed numbers of bytes. These include types like Int#, Char# and Addr#.
  2. Unlifted types: values are pointers, but strictly evaluated. These include types like MutVar# s a, Array# a, and MVar# s a.
  3. Lifted types: values are pointers, lazily evaluated.

Certain lifted types are really just thin wrappers around unboxed types (we can call these category 3a) or unlifted pointer types (we can call these category 3b) Category 3a includes Int, Char, and `Ptr a`, while category 3b includes IORef a, Data.Primitive.Array.Array a, and MVar a.

Types in category 3a can be stored efficiently in a Data.Primitive.PrimArray.PrimArray, removing and applying wrappers as required. This module provides the same facility for types in category 3b.

Synopsis

Types

data UnliftedArray_ unlifted_a a Source #

An UnliftedArray_ a unlifted_a represents an array of values of a lifted type a that wrap values of an unlifted type unlifted_a. It is expected that unlifted_a ~ Unlifted a, but imposing that constraint here would force the type roles to nominal, which is often undesirable when arrays are used as components of larger datatypes.

Constructors

UnliftedArray (UnliftedArray# unlifted_a) 

Instances

Instances details
(PrimUnlifted a, unlifted_a ~ Unlifted a) => Monoid (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Methods

mempty :: UnliftedArray_ unlifted_a a #

mappend :: UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a #

mconcat :: [UnliftedArray_ unlifted_a a] -> UnliftedArray_ unlifted_a a #

(PrimUnlifted a, unlifted_a ~ Unlifted a) => Semigroup (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Methods

(<>) :: UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a #

sconcat :: NonEmpty (UnliftedArray_ unlifted_a a) -> UnliftedArray_ unlifted_a a #

stimes :: Integral b => b -> UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a #

(PrimUnlifted a, unlifted_a ~ Unlifted a) => IsList (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Associated Types

type Item (UnliftedArray_ unlifted_a a) #

Methods

fromList :: [Item (UnliftedArray_ unlifted_a a)] -> UnliftedArray_ unlifted_a a #

fromListN :: Int -> [Item (UnliftedArray_ unlifted_a a)] -> UnliftedArray_ unlifted_a a #

toList :: UnliftedArray_ unlifted_a a -> [Item (UnliftedArray_ unlifted_a a)] #

(Show a, PrimUnlifted a, unlifted_a ~ Unlifted a) => Show (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Methods

showsPrec :: Int -> UnliftedArray_ unlifted_a a -> ShowS #

show :: UnliftedArray_ unlifted_a a -> String #

showList :: [UnliftedArray_ unlifted_a a] -> ShowS #

(Eq a, PrimUnlifted a, unlifted_a ~ Unlifted a) => Eq (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Methods

(==) :: UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a -> Bool #

(/=) :: UnliftedArray_ unlifted_a a -> UnliftedArray_ unlifted_a a -> Bool #

unlifted_a ~ Unlifted a => PrimUnlifted (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Associated Types

type Unlifted (UnliftedArray_ unlifted_a a) :: UnliftedType Source #

Methods

toUnlifted# :: UnliftedArray_ unlifted_a a -> Unlifted (UnliftedArray_ unlifted_a a) Source #

fromUnlifted# :: Unlifted (UnliftedArray_ unlifted_a a) -> UnliftedArray_ unlifted_a a Source #

type Item (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

type Item (UnliftedArray_ unlifted_a a) = a
type Unlifted (UnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

type Unlifted (UnliftedArray_ unlifted_a a) = UnliftedArray# unlifted_a

type UnliftedArray a = UnliftedArray_ (Unlifted a) a Source #

A type synonym for an UnliftedArray_ containing lifted values of a particular type. As a general rule, this type synonym should not be used in class instances—use UnliftedArray_ with an equality constraint instead. It also should not be used when defining newtypes or datatypes, unless those will have restrictive type roles regardless—use UnliftedArray_ instead.

data MutableUnliftedArray_ unlifted_a s a Source #

A mutable version of UnliftedArray_.

Constructors

MutableUnliftedArray (MutableUnliftedArray# s unlifted_a) 

Instances

Instances details
unlifted_a ~ Unlifted a => Eq (MutableUnliftedArray_ unlifted_a s a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Methods

(==) :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool #

(/=) :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool #

unlifted_a ~ Unlifted a => PrimUnlifted (MutableUnliftedArray_ unlifted_a s a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

Associated Types

type Unlifted (MutableUnliftedArray_ unlifted_a s a) :: UnliftedType Source #

Methods

toUnlifted# :: MutableUnliftedArray_ unlifted_a s a -> Unlifted (MutableUnliftedArray_ unlifted_a s a) Source #

fromUnlifted# :: Unlifted (MutableUnliftedArray_ unlifted_a s a) -> MutableUnliftedArray_ unlifted_a s a Source #

type Unlifted (MutableUnliftedArray_ unlifted_a s a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Array.ST

type Unlifted (MutableUnliftedArray_ unlifted_a s a) = MutableUnliftedArray# s unlifted_a

Operations

newUnliftedArray Source #

Arguments

:: (PrimMonad m, PrimUnlifted a) 
=> Int

size

-> a

initial value

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray with the specified value as initial contents.

unsafeNewUnliftedArray Source #

Arguments

:: PrimMonad m 
=> Int

size

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray. This function is unsafe because it initializes all elements of the array as pointers to the empty array. Attempting to read one of these elements before writing to it is in effect an unsafe coercion from UnliftedArray a to the element type.

sameMutableUnliftedArray :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool Source #

Determines whether two MutableUnliftedArray_ values are the same. This is object/pointer identity, not based on the contents.

unsafeFreezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> m (UnliftedArray a) Source #

Freezes a MutableUnliftedArray, yielding an UnliftedArray. This simply marks the array as frozen in place, so it should only be used when no further modifications to the mutable array will be performed.

freezeUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

source

-> Int

offset

-> Int

length

-> m (UnliftedArray a) 

Freezes a portion of a MutableUnliftedArray, yielding an UnliftedArray. This operation is safe, in that it copies the frozen portion, and the existing mutable array may still be used afterward.

thawUnliftedArray Source #

Arguments

:: PrimMonad m 
=> UnliftedArray a

source

-> Int

offset

-> Int

length

-> m (MutableUnliftedArray (PrimState m) a) 

Thaws a portion of an UnliftedArray, yielding a MutableUnliftedArray. This copies the thawed portion, so mutations will not affect the original array.

unsafeThawUnliftedArray Source #

Arguments

:: PrimMonad m 
=> UnliftedArray a

source

-> m (MutableUnliftedArray (PrimState m) a) 

Thaws an UnliftedArray, yielding a MutableUnliftedArray. This does not make a copy.

setUnliftedArray Source #

Arguments

:: (PrimMonad m, PrimUnlifted a) 
=> MutableUnliftedArray (PrimState m) a

destination

-> a

value to fill with

-> Int

offset

-> Int

length

-> m () 

copyUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

destination

-> Int

offset into destination

-> UnliftedArray a

source

-> Int

offset into source

-> Int

number of elements to copy

-> m () 

Copies the contents of an immutable array into a mutable array.

copyMutableUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

destination

-> Int

offset into destination

-> MutableUnliftedArray (PrimState m) a

source

-> Int

offset into source

-> Int

number of elements to copy

-> m () 

Copies the contents of one mutable array into another.

cloneUnliftedArray Source #

Arguments

:: UnliftedArray a

source

-> Int

offset

-> Int

length

-> UnliftedArray a 

Creates a copy of a portion of an UnliftedArray_

cloneMutableUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

source

-> Int

offset

-> Int

length

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray containing a copy of a portion of another mutable array.

runUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a Source #

Execute a stateful computation and freeze the resulting array.

dupableRunUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a Source #

Execute a stateful computation and freeze the resulting array. It is possible, but unlikely, that the computation will be run multiple times in multiple threads.

List Conversion

unliftedArrayToList :: PrimUnlifted a => UnliftedArray a -> [a] Source #

Convert the unlifted array to a list.

Folding

foldrUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b Source #

foldrUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b Source #

Strict right-associated fold over the elements of an 'UnliftedArray.

foldlUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b Source #

Lazy left-associated fold over the elements of an UnliftedArray_.

foldlUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b Source #

Strict left-associated fold over the elements of an UnliftedArray_.

foldlUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> UnliftedArray a -> m b Source #

Strict effectful left-associated fold over the elements of an UnliftedArray_.

Traversals

traverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> UnliftedArray a -> m () Source #

Effectfully traverse the elements of an UnliftedArray_, discarding the resulting values.

itraverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> UnliftedArray a -> m () Source #

Effectful indexed traversal of the elements of an UnliftedArray_, discarding the resulting values.

Mapping

mapUnliftedArray :: (PrimUnlifted a, PrimUnlifted b) => (a -> b) -> UnliftedArray a -> UnliftedArray b Source #

Map over the elements of an UnliftedArray_.