PrimitiveArray-0.9.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.BitSetClasses

Contents

Description

A collection of a number of data types and type classes shared by all bitset variants.

Synopsis

Boundaries, the interface(s) for bitsets.

newtype Boundary boundaryType ioc 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

Boundary 

Fields

Instances
Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

IndexStream z => IndexStream (z :. Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

streamUp :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

streamDown :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

Eq (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

(==) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(/=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

Num (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

(+) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

(-) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

(*) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

negate :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

abs :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

signum :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

fromInteger :: Integer -> Boundary boundaryType ioc #

Ord (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

compare :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Ordering #

(<) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(<=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(>) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(>=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

max :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

min :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

Show (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

showsPrec :: Int -> Boundary i t -> ShowS #

show :: Boundary i t -> String #

showList :: [Boundary i t] -> ShowS #

Generic (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Associated Types

type Rep (Boundary boundaryType ioc) :: Type -> Type #

Methods

from :: Boundary boundaryType ioc -> Rep (Boundary boundaryType ioc) x #

to :: Rep (Boundary boundaryType ioc) x -> Boundary boundaryType ioc #

Hashable (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

hashWithSalt :: Int -> Boundary i t -> Int #

hash :: Boundary i t -> Int #

ToJSON (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

FromJSON (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Binary (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

put :: Boundary i t -> Put #

get :: Get (Boundary i t) #

putList :: [Boundary i t] -> Put #

Serialize (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

put :: Putter (Boundary i t) #

get :: Get (Boundary i t) #

NFData (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

rnf :: Boundary i t -> () #

Unbox (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

IndexStream (Z :. Boundary k2 I) => IndexStream (Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Index (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Associated Types

data LimitType (Boundary i t) :: Type Source #

data MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

type Rep (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

type Rep (Boundary boundaryType ioc) = D1 (MetaData "Boundary" "Data.PrimitiveArray.Index.BitSetClasses" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "Boundary" PrefixI True) (S1 (MetaSel (Just "getBoundary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

data LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

streamUpBndMk :: Monad m => b -> p -> a -> m (a, b) Source #

streamUpBndStep :: Monad m => p -> Int -> (a, Int) -> m (Step (a, Int) (a :. Boundary boundaryType ioc)) Source #

streamDownBndMk :: Monad m => p -> b -> a -> m (a, b) Source #

streamDownBndStep :: Monad m => Int -> p -> (a, Int) -> m (Step (a, Int) (a :. Boundary boundaryType ioc)) Source #

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

Moving indices within sets.

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 :: Int -> Int -> 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 :: Int -> Int -> 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.

Instances
SetPredSucc (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

setSucc :: Int -> Int -> BitSet t -> Maybe (BitSet t) Source #

setPred :: Int -> Int -> BitSet t -> Maybe (BitSet t) Source #

SetPredSucc (BitSet1 t ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

setSucc :: Int -> Int -> BitSet1 t ioc -> Maybe (BitSet1 t ioc) Source #

setPred :: Int -> Int -> BitSet1 t ioc -> Maybe (BitSet1 t ioc) Source #

type family Mask s :: * Source #

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

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

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 #