foundation-0.0.15: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Array.Internal

Contents

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

PrimType ty => IsList (UArray ty) 

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) 

Methods

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

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

Data ty => Data (UArray ty) 

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 :: (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) 

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) 

Methods

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

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Monoid (UArray ty) 

Methods

mempty :: UArray ty #

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

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

NormalForm (UArray ty) 

Methods

toNormalForm :: UArray ty -> () #

PrimType ty => Fold1able (UArray ty) # 

Methods

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

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

PrimType ty => Foldable (UArray ty) # 

Methods

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

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

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

PrimType ty => IndexedCollection (UArray ty) # 

Methods

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

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

PrimType ty => InnerFunctor (UArray ty) # 

Methods

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

PrimType ty => Copy (UArray ty) # 

Methods

copy :: UArray ty -> UArray ty #

PrimType ty => Collection (UArray ty) # 

Methods

null :: UArray ty -> Bool #

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

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

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

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

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

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

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

PrimType ty => Sequential (UArray ty) # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

reverse :: UArray ty -> UArray ty #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PrimType ty => Zippable (UArray ty) # 

Methods

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

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

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 #

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 #

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 #

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 #

PrimType ty => Buildable (UArray ty) # 

Associated Types

type Mutable (UArray ty) :: * -> * #

type Step (UArray ty) :: * #

Methods

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

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

PrimType a => Hashable (UArray a) # 

Methods

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

type Item (UArray ty) 
type Item (UArray ty) = ty
type Element (UArray ty) # 
type Element (UArray ty) = ty
type Mutable (UArray ty) # 
type Mutable (UArray ty) = MUArray ty
type Step (UArray ty) # 
type Step (UArray ty) = ty

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

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.