discrimination-0.4.1: Fast generic linear-time sorting, joins and container construction.
Copyright(c) Edward Kmett 2015
LicenseBSD-style
MaintainerEdward Kmett <ekmett@gmail.com>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Discrimination.Internal.SmallArray

Description

Small primitive boxed arrays

Synopsis

Documentation

data SmallArray a Source #

Boxed arrays

Constructors

SmallArray (SmallArray# a) 

Instances

Instances details
Functor SmallArray Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Methods

fmap :: (a -> b) -> SmallArray a -> SmallArray b #

(<$) :: a -> SmallArray b -> SmallArray a #

Foldable SmallArray Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Methods

fold :: Monoid m => SmallArray m -> m #

foldMap :: Monoid m => (a -> m) -> SmallArray a -> m #

foldMap' :: Monoid m => (a -> m) -> SmallArray a -> m #

foldr :: (a -> b -> b) -> b -> SmallArray a -> b #

foldr' :: (a -> b -> b) -> b -> SmallArray a -> b #

foldl :: (b -> a -> b) -> b -> SmallArray a -> b #

foldl' :: (b -> a -> b) -> b -> SmallArray a -> b #

foldr1 :: (a -> a -> a) -> SmallArray a -> a #

foldl1 :: (a -> a -> a) -> SmallArray a -> a #

toList :: SmallArray a -> [a] #

null :: SmallArray a -> Bool #

length :: SmallArray a -> Int #

elem :: Eq a => a -> SmallArray a -> Bool #

maximum :: Ord a => SmallArray a -> a #

minimum :: Ord a => SmallArray a -> a #

sum :: Num a => SmallArray a -> a #

product :: Num a => SmallArray a -> a #

Traversable SmallArray Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Methods

traverse :: Applicative f => (a -> f b) -> SmallArray a -> f (SmallArray b) #

sequenceA :: Applicative f => SmallArray (f a) -> f (SmallArray a) #

mapM :: Monad m => (a -> m b) -> SmallArray a -> m (SmallArray b) #

sequence :: Monad m => SmallArray (m a) -> m (SmallArray a) #

IsList (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Associated Types

type Item (SmallArray a) #

Eq a => Eq (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Methods

(==) :: SmallArray a -> SmallArray a -> Bool #

(/=) :: SmallArray a -> SmallArray a -> Bool #

Ord a => Ord (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Read a => Read (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Show a => Show (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

NFData a => NFData (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

Methods

rnf :: SmallArray a -> () #

type Item (SmallArray a) Source # 
Instance details

Defined in Data.Discrimination.Internal.SmallArray

type Item (SmallArray a) = a

data SmallMutableArray s a Source #

Mutable boxed arrays associated with a primitive state token.

newSmallArray :: PrimMonad m => Int -> a -> m (SmallMutableArray (PrimState m) a) Source #

Create a new mutable array of the specified size and initialise all elements with the given value.

readSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m a Source #

Read a value from the array at the given index.

writeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> a -> m () Source #

Write a value to the array at the given index.

indexSmallArray :: SmallArray a -> Int -> a Source #

Read a value from the immutable array at the given index.

indexSmallArrayM :: Monad m => SmallArray a -> Int -> m a Source #

Monadically read a value from the immutable array at the given index. This allows us to be strict in the array while remaining lazy in the read element which is very useful for collective operations. Suppose we want to copy an array. We could do something like this:

copy marr arr ... = do ...
                       writeSmallArray marr i (indexSmallArray arr i) ...
                       ...

But since primitive arrays are lazy, the calls to indexSmallArray will not be evaluated. Rather, marr will be filled with thunks each of which would retain a reference to arr. This is definitely not what we want!

With indexSmallArrayM, we can instead write

copy marr arr ... = do ...
                       x <- indexSmallArrayM arr i
                       writeSmallArray marr i x
                       ...

Now, indexing is executed immediately although the returned element is still not evaluated.

unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a) Source #

Convert a mutable array to an immutable one without copying. The array should not be modified after the conversion.

unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a) Source #

Convert an immutable array to an mutable one without copying. The immutable array should not be used after the conversion.

sameSmallMutableArray :: SmallMutableArray s a -> SmallMutableArray s a -> Bool Source #

Check whether the two arrays refer to the same memory block.

copySmallArray Source #

Arguments

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

destination array

-> Int

offset into destination array

-> SmallArray a

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

Copy a slice of an immutable array to a mutable array.

copySmallMutableArray Source #

Arguments

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

destination array

-> Int

offset into destination array

-> SmallMutableArray (PrimState m) a

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

Copy a slice of a mutable array to another array. The two arrays may not be the same.

cloneSmallArray Source #

Arguments

:: SmallArray a

source array

-> Int

offset into destination array

-> Int

number of elements to copy

-> SmallArray a 

Return a newly allocated SmallArray with the specified subrange of the provided SmallArray. The provided SmallArray should contain the full subrange specified by the two Ints, but this is not checked.

cloneSmallMutableArray Source #

Arguments

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

source array

-> Int

offset into destination array

-> Int

number of elements to copy

-> m (SmallMutableArray (PrimState m) a) 

Return a newly allocated SmallMutableArray. with the specified subrange of the provided SmallMutableArray. The provided SmallMutableArray should contain the full subrange specified by the two Ints, but this is not checked.