foundation-0.0.26.1: Alternative prelude with batteries and no dependencies
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Array.Internal

Description

Give access to Array non public functions which can be used to make certains optimisations.

Most of what is available here has no guarantees of stability. Anything can be removed and changed.

Synopsis

Documentation

data UArray ty #

An array of type built on top of GHC primitive.

The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface

Constructors

UArray !(Offset ty) !(CountOf ty) !(UArrayBackend ty) 

Instances

Instances details
From String (UArray Word8) 
Instance details

Defined in Basement.From

Methods

from :: String -> UArray Word8 #

From AsciiString (UArray Word8) 
Instance details

Defined in Basement.From

PrimType ty => IsList (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Associated Types

type Item (UArray ty) #

Methods

fromList :: [Item (UArray ty)] -> UArray ty #

fromListN :: Int -> [Item (UArray ty)] -> UArray ty #

toList :: UArray ty -> [Item (UArray ty)] #

(PrimType ty, Eq ty) => Eq (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

(==) :: UArray ty -> UArray ty -> Bool #

(/=) :: UArray ty -> UArray ty -> Bool #

Data ty => Data (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UArray ty -> c (UArray ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray ty) #

toConstr :: UArray ty -> Constr #

dataTypeOf :: UArray ty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UArray ty)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UArray ty)) #

gmapT :: (forall b. Data b => b -> b) -> UArray ty -> UArray ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> UArray ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UArray ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

(PrimType ty, Ord ty) => Ord (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

compare :: UArray ty -> UArray ty -> Ordering #

(<) :: UArray ty -> UArray ty -> Bool #

(<=) :: UArray ty -> UArray ty -> Bool #

(>) :: UArray ty -> UArray ty -> Bool #

(>=) :: UArray ty -> UArray ty -> Bool #

max :: UArray ty -> UArray ty -> UArray ty #

min :: UArray ty -> UArray ty -> UArray ty #

(PrimType ty, Show ty) => Show (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Semigroup (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

(<>) :: UArray ty -> UArray ty -> UArray ty #

sconcat :: NonEmpty (UArray ty) -> UArray ty #

stimes :: Integral b => b -> UArray ty -> UArray ty #

PrimType ty => Monoid (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

NormalForm (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

toNormalForm :: UArray ty -> () #

PrimType ty => Copy (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: UArray ty -> UArray ty Source #

PrimType ty => Collection (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Collection

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> CountOf (Element (UArray ty)) Source #

elem :: (Eq a, a ~ Element (UArray ty)) => Element (UArray ty) -> UArray ty -> Bool Source #

notElem :: (Eq a, a ~ Element (UArray ty)) => Element (UArray ty) -> UArray ty -> Bool Source #

maximum :: (Ord a, a ~ Element (UArray ty)) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

minimum :: (Ord a, a ~ Element (UArray ty)) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

any :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

all :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

PrimType ty => Buildable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Buildable

Associated Types

type Mutable (UArray ty) :: Type -> Type Source #

type Step (UArray ty) Source #

Methods

append :: forall (prim :: Type -> Type) err. PrimMonad prim => Element (UArray ty) -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () -> prim (Either err (UArray ty)) Source #

PrimType ty => Fold1able (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl1' :: (Element (UArray ty) -> Element (UArray ty) -> Element (UArray ty)) -> NonEmpty (UArray ty) -> Element (UArray ty) Source #

foldr1 :: (Element (UArray ty) -> Element (UArray ty) -> Element (UArray ty)) -> NonEmpty (UArray ty) -> Element (UArray ty) Source #

PrimType ty => Foldable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => IndexedCollection (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: UArray ty -> Offset (Element (UArray ty)) -> Maybe (Element (UArray ty)) Source #

findIndex :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Offset (Element (UArray ty))) Source #

PrimType ty => InnerFunctor (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.InnerFunctor

Methods

imap :: (Element (UArray ty) -> Element (UArray ty)) -> UArray ty -> UArray ty Source #

PrimType ty => Sequential (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

splitOn :: (Element (UArray ty) -> Bool) -> UArray ty -> [UArray ty] Source #

break :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakElem :: Element (UArray ty) -> UArray ty -> (UArray ty, UArray ty) Source #

takeWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

dropWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

intersperse :: Element (UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element (UArray ty) -> UArray ty -> Element (UArray ty) Source #

span :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

spanEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

filter :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

partition :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe (Element (UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe (UArray ty, Element (UArray ty)) Source #

snoc :: UArray ty -> Element (UArray ty) -> UArray ty Source #

cons :: Element (UArray ty) -> UArray ty -> UArray ty Source #

find :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Element (UArray ty)) Source #

sortBy :: (Element (UArray ty) -> Element (UArray ty) -> Ordering) -> UArray ty -> UArray ty Source #

singleton :: Element (UArray ty) -> UArray ty Source #

head :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

last :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

tail :: NonEmpty (UArray ty) -> UArray ty Source #

init :: NonEmpty (UArray ty) -> UArray ty Source #

replicate :: CountOf (Element (UArray ty)) -> Element (UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

stripPrefix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

PrimType ty => Zippable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Zippable

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (UArray ty)) -> a -> b -> UArray ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (UArray ty)) -> a -> b -> c -> UArray ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (UArray ty)) -> a -> b -> c -> d -> UArray ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (UArray ty)) -> a -> b -> c -> d -> e -> UArray ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> UArray ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> g -> UArray ty Source #

PrimType a => Hashable (UArray a) Source # 
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => UArray a -> st -> st Source #

TryFrom (UArray Word8) String 
Instance details

Defined in Basement.From

PrimType ty => From (Array ty) (UArray ty) 
Instance details

Defined in Basement.From

Methods

from :: Array ty -> UArray ty #

PrimType ty => From (UArray ty) (Block ty) 
Instance details

Defined in Basement.From

Methods

from :: UArray ty -> Block ty #

PrimType ty => From (UArray ty) (Array ty) 
Instance details

Defined in Basement.From

Methods

from :: UArray ty -> Array ty #

PrimType ty => From (Block ty) (UArray ty) 
Instance details

Defined in Basement.From

Methods

from :: Block ty -> UArray ty #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) 
Instance details

Defined in Basement.From

Methods

tryFrom :: UArray ty -> Maybe (BlockN n ty) #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) 
Instance details

Defined in Basement.From

Methods

from :: BlockN n ty -> UArray ty #

type Item (UArray ty) 
Instance details

Defined in Basement.UArray.Base

type Item (UArray ty) = ty
type Element (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (UArray ty) = ty
type Mutable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Buildable

type Mutable (UArray ty) = MUArray ty
type Step (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Buildable

type Step (UArray ty) = ty

fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty #

Create a foreign UArray from foreign memory and given offset/size

No check are performed to make sure this is valid, so this is unsafe.

This is particularly useful when dealing with foreign memory and ByteString

withPtr :: forall ty prim a. (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a #

Get a Ptr pointing to the data in the UArray.

Since a UArray is immutable, this Ptr shouldn't be to use to modify the contents

If the UArray is pinned, then its address is returned as is, however if it's unpinned, a pinned copy of the UArray is made before getting the address.

copyToPtr #

Arguments

:: (PrimType ty, PrimMonad prim) 
=> UArray ty

the source array to copy

-> Ptr ty

The destination address where the copy is going to start

-> prim () 

Copy all the block content to the memory starting at the destination address

recast :: (PrimType a, PrimType b) => UArray a -> UArray b #

Recast an array of type a to an array of b

a and b need to have the same size otherwise this raise an async exception

Mutable facilities

new :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) #

Create a new mutable array of size @n.

When memory for a new array is allocated, we decide if that memory region should be pinned (will not be copied around by GC) or unpinned (can be moved around by GC) depending on its size.

You can change the threshold value used by setting the environment variable HS_FOUNDATION_UARRAY_UNPINNED_MAX.

newPinned :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) #

Create a new pinned mutable array of size @n.

all the cells are uninitialized and could contains invalid values.

All mutable arrays are allocated on a 64 bits aligned addresses

withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a #

Create a pointer on the beginning of the mutable array and call a function f.

The mutable buffer can be mutated by the f function and the change will be reflected in the mutable array

If the mutable array is unpinned, a trampoline buffer is created and the data is only copied when f return.