PrimitiveArray-0.7.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.Set

Contents

Description

Set with and without interfaces. We provide instances for sets, and sets with one or two interfaces. The First and Last annotation is purely cosmetical (apart from introducing type safety).

Synopsis

newtypes, data types, classes.

newtype Interface t Source

Certain sets have an interface, a particular element with special meaning. In this module, certain `meanings' are already provided. These include a First element and a Last element. We phantom-type these to reduce programming overhead.

Constructors

Iter 

Fields

getIter :: Int
 

data First Source

Declare the interface to be the start of a path.

data Last Source

Declare the interface to be the end of a path.

data Any Source

Declare the interface to match anything.

TODO needed? want to use later in ADPfusion

data BS1 i t Source

A bitset with one interface.

Constructors

BS1 !(BitSet t) !(Interface i) 

data BS2 i j t Source

A bitset with two interfaces.

Constructors

BS2 !(BitSet t) !(Interface i) !(Interface j) 

Instances

SetPredSucc (Fixed (BS2 i j t)) Source 
IndexStream z => IndexStream ((:.) z (BS2 i j C)) Source 
IndexStream z => IndexStream ((:.) z (BS2 i j O)) Source 
IndexStream z => IndexStream ((:.) z (BS2 i j I)) Source 
Show (BS2 i j t) Source 
Arbitrary (BS2 i j t) Source 
IndexStream ((:.) Z (BS2 i j t)) => IndexStream (BS2 i j t) Source 
Index (BS2 i j t) Source 
ApplyMask (BS2 i j t) Source 
SetPredSucc (BS2 i j t) Source 
type Mask (BS2 i j t) = BitSet t Source 

class SetPredSucc s where Source

Successor and Predecessor for sets. Designed as a class to accomodate sets with interfaces and without interfaces with one function.

The functions are not written recursively, as we currently only have three cases, and we do not want to "reset" while generating successors and predecessors.

Note that sets have a partial order. Within the group of element with the same popCount, we use popPermutation which has the same stepping order for both, setSucc and setPred.

Methods

setSucc :: s -> s -> s -> Maybe s Source

Set successor. The first argument is the lower set limit, the second the upper set limit, the third the current set.

setPred :: s -> s -> s -> Maybe s Source

Set predecessor. The first argument is the lower set limit, the second the upper set limit, the third the current set.

type family Mask s :: * Source

Masks are used quite often for different types of bitsets. We liberate them as a type family.

Instances

type Mask (BitSet t) = BitSet t Source 
type Mask (BS1 i t) = BitSet t Source 
type Mask (BS2 i j t) = BitSet t Source 

data Fixed t Source

Fixed allows us to fix some or all bits of a bitset, thereby providing succ/pred operations which are only partially free.

The mask is lazy, this allows us to have undefined for l and h.

f = getFixedMask .&. getFixed are the fixed bits. n = getFixed .&. complement getFixedMask are the free bits. to = complement getFixed is the to move mask n' = popShiftR to n yields the population after the move p = popPermutation undefined n' yields the new population permutation p' = popShiftL to p yields the population moved back final = p' .|. f

Constructors

Fixed 

Fields

getFixedMask :: Mask t
 
getFixed :: !t
 

Instances

(Unbox t0, Unbox (Mask t0)) => Vector Vector (Fixed t) Source 
(Unbox t0, Unbox (Mask t0)) => MVector MVector (Fixed t) Source 
(Eq t, Eq (Mask t)) => Eq (Fixed t) Source 
(Ord t, Ord (Mask t)) => Ord (Fixed t) Source 
(Read t, Read (Mask t)) => Read (Fixed t) Source 
(Show t, Show (Mask t)) => Show (Fixed t) Source 
(Generic t, Generic (Mask t)) => Generic (Fixed t) Source 
(Arbitrary t, Arbitrary (Mask t)) => Arbitrary (Fixed t) Source 
(Generic t, Generic (Mask t), Binary t, Binary (Mask t)) => Binary (Fixed t) Source 
(Generic t, Generic (Mask t), Serialize t, Serialize (Mask t)) => Serialize (Fixed t) Source 
NFData (Fixed t) Source 
(Generic t, Generic (Mask t), Hashable t, Hashable (Mask t)) => Hashable (Fixed t) Source 
(Unbox t0, Unbox (Mask t0)) => Unbox (Fixed t) Source 
SetPredSucc (Fixed (BS2 i j t)) Source 
SetPredSucc (Fixed (BS1 i t)) Source 
SetPredSucc (Fixed (BitSet t)) Source 
data MVector s0 (Fixed t0) = MV_Fixed (MVector s (Mask t, t)) Source 
type Rep (Fixed t) Source 
data Vector (Fixed t0) = V_Fixed (Vector (Mask t, t)) Source 

class ApplyMask s where Source

Assuming a bitset on bits [0 .. highbit], we can apply a mask that stretches out those bits over [0 .. higherBit] with highbit <= higherBit. Any active interfaces are correctly set as well.

Methods

applyMask :: Mask s -> s -> s Source

Instances

Instances

streamUpBsMk :: (Monad m, Ord a) => a -> a -> t -> m (t, Maybe a) Source

streamUpBsStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

streamDownBsMk :: (Monad m, Ord a) => a -> a -> t -> m (t, Maybe a) Source

streamDownBsStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

BS1

streamUpBsIMk :: Monad m => BS1 a i -> BS1 b i -> z -> m (z, Maybe (BS1 c i)) Source

streamUpBsIStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

streamDownBsIMk :: Monad m => BS1 a i -> BS1 b i -> z -> m (z, Maybe (BS1 c i)) Source

streamDownBsIStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

BS2

streamUpBsIiMk :: Monad m => BS2 a b i -> BS2 c d i -> z -> m (z, Maybe (BS2 e f i)) Source

streamUpBsIiStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

streamDownBsIiMk :: Monad m => BS2 a b i -> BS2 c d i -> z -> m (z, Maybe (BS2 e f i)) Source

streamDownBsIiStep :: (Monad m, SetPredSucc s) => s -> s -> (t, Maybe s) -> m (Step (t, Maybe s) (t :. s)) Source

Set predecessor and successor