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

Data.Primitive.Unlifted.SmallArray.ST

Description

A version of the SmallArray interface specialized to ST. This is intended primarily so library developers can easily check whether the basic operations are unboxed properly, but its more constrained type signatures also offer somewhat better type inference where applicable.

Synopsis

Types

data SmallUnliftedArray_ unlifted_a a Source #

A SmallUnliftedArray_ 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

SmallUnliftedArray (SmallUnliftedArray# unlifted_a) 

Instances

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Methods

mempty :: SmallUnliftedArray_ unlifted_a a #

mappend :: SmallUnliftedArray_ unlifted_a a -> SmallUnliftedArray_ unlifted_a a -> SmallUnliftedArray_ unlifted_a a #

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Methods

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

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

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Associated Types

type Item (SmallUnliftedArray_ unlifted_a a) #

Methods

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

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

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Methods

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

show :: SmallUnliftedArray_ unlifted_a a -> String #

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Methods

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

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Associated Types

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

type Item (SmallUnliftedArray_ unlifted_a a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.SmallArray.ST

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

type Unlifted (SmallUnliftedArray_ unlifted_a a) = SmallUnliftedArray# unlifted_a

type SmallUnliftedArray a = SmallUnliftedArray_ (Unlifted a) a Source #

A type synonym for a SmallUnliftedArray_ containing lifted values of a particular type. As a general rule, this type synonym should not be used in class instances—use SmallUnliftedArray_ 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 SmallUnliftedArray_ instead.

data SmallMutableUnliftedArray_ unlifted_a s a Source #

Instances

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Methods

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

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Associated Types

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

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

Defined in Data.Primitive.Unlifted.SmallArray.ST

Operations

newSmallUnliftedArray Source #

Arguments

:: PrimUnlifted a 
=> Int

size

-> a

initial value

-> ST s (SmallMutableUnliftedArray s a) 

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

unsafeNewSmallUnliftedArray Source #

Arguments

:: Int

size

-> ST s (SmallMutableUnliftedArray s 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.

sizeofSmallUnliftedArray :: SmallUnliftedArray_ unlifted_e e -> Int Source #

Yields the length of an UnliftedArray.

getSizeofSmallMutableUnliftedArray :: SmallMutableUnliftedArray s e -> ST s Int Source #

Yields the length of a MutableUnliftedArray.

sameSmallMutableUnliftedArray :: SmallMutableUnliftedArray_ unlifted_a s a -> SmallMutableUnliftedArray_ unlifted_a s a -> Bool Source #

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

shrinkSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> ST s () Source #

Shrink a mutable array to the specified size. The new size argument must be less than or equal to the current size.

unsafeFreezeSmallUnliftedArray :: SmallMutableUnliftedArray s a -> ST s (SmallUnliftedArray a) Source #

Freezes a SmallMutableUnliftedArray_, yielding a SmallUnliftedArray_. 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.

freezeSmallUnliftedArray Source #

Arguments

:: SmallMutableUnliftedArray s a

source

-> Int

offset

-> Int

length

-> ST s (SmallUnliftedArray 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.

thawSmallUnliftedArray Source #

Arguments

:: SmallUnliftedArray a

source

-> Int

offset

-> Int

length

-> ST s (SmallMutableUnliftedArray s a) 

Thaws a portion of a SmallUnliftedArray_, yielding a SmallMutableUnliftedArray_. This copies the thawed portion, so mutations will not affect the original array.

unsafeThawSmallUnliftedArray Source #

Arguments

:: SmallUnliftedArray a

source

-> ST s (SmallMutableUnliftedArray s a) 

Thaws a SmallUnliftedArray_, yielding a SmallMutableUnliftedArray_. This does not make a copy.

setSmallUnliftedArray Source #

Arguments

:: PrimUnlifted a 
=> SmallMutableUnliftedArray s a

destination

-> a

value to fill with

-> Int

offset

-> Int

length

-> ST s () 

copySmallUnliftedArray Source #

Arguments

:: SmallMutableUnliftedArray s a

destination

-> Int

offset into destination

-> SmallUnliftedArray a

source

-> Int

offset into source

-> Int

number of elements to copy

-> ST s () 

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

copySmallMutableUnliftedArray Source #

Arguments

:: SmallMutableUnliftedArray s a

destination

-> Int

offset into destination

-> SmallMutableUnliftedArray s a

source

-> Int

offset into source

-> Int

number of elements to copy

-> ST s () 

Copies the contents of one mutable array into another.

cloneSmallUnliftedArray Source #

Arguments

:: SmallUnliftedArray a

source

-> Int

offset

-> Int

length

-> SmallUnliftedArray a 

Creates a copy of a portion of a SmallUnliftedArray_

cloneSmallMutableUnliftedArray Source #

Arguments

:: SmallMutableUnliftedArray s a

source

-> Int

offset

-> Int

length

-> ST s (SmallMutableUnliftedArray s a) 

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

runSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray a Source #

Execute a stateful computation and freeze the resulting array.

dupableRunSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray 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

smallUnliftedArrayToList :: PrimUnlifted a => SmallUnliftedArray a -> [a] Source #

Convert the unlifted array to a list.

Folding

foldrSmallUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b Source #

foldrSmallUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b Source #

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

foldlSmallUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b Source #

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

foldlSmallUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b Source #

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

foldlSmallUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> SmallUnliftedArray a -> m b Source #

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

Traversals

traverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> SmallUnliftedArray a -> m () Source #

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

itraverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> SmallUnliftedArray a -> m () Source #

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

Mapping