PrimitiveArray-0.10.1.0: Efficient multidimensional arrays
Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.BitSet1

Description

A bitset with one interface. This includes the often-encountered case where {u,v},{v}, or sets with a single edge between the old set and a new singleton set are required. Uses are Hamiltonian path problems, and TSP, among others.

Synopsis

Documentation

data BitSet1 i ioc Source #

The bitset with one interface or boundary.

Constructors

BitSet1 

Fields

Instances

Instances details
Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (BitSet1 i ioc) -> m (Vector (BitSet1 i ioc)) #

basicUnsafeThaw :: PrimMonad m => Vector (BitSet1 i ioc) -> m (Mutable Vector (PrimState m) (BitSet1 i ioc)) #

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

basicUnsafeIndexM :: Monad m => Vector (BitSet1 i ioc) -> Int -> m (BitSet1 i ioc) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (BitSet1 i ioc) -> Vector (BitSet1 i ioc) -> m () #

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> BitSet1 i ioc -> m (MVector (PrimState m) (BitSet1 i ioc)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> Int -> m (BitSet1 i ioc) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> Int -> BitSet1 i ioc -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> BitSet1 i ioc -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> MVector (PrimState m) (BitSet1 i ioc) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> MVector (PrimState m) (BitSet1 i ioc) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (BitSet1 i ioc) -> Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

SetPredSucc (FixedMask (BitSet1 t ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

IndexStream z => IndexStream (z :. BitSet1 i O) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i O) -> LimitType (z :. BitSet1 i O) -> Stream m (z :. BitSet1 i O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i O) -> LimitType (z :. BitSet1 i O) -> Stream m (z :. BitSet1 i O) Source #

IndexStream z => IndexStream (z :. BitSet1 i I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

Eq (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

(==) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(/=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

Ord (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

compare :: BitSet1 i ioc -> BitSet1 i ioc -> Ordering #

(<) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(<=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(>) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(>=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

max :: BitSet1 i ioc -> BitSet1 i ioc -> BitSet1 i ioc #

min :: BitSet1 i ioc -> BitSet1 i ioc -> BitSet1 i ioc #

Show (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> BitSet1 i ioc -> ShowS #

show :: BitSet1 i ioc -> String #

showList :: [BitSet1 i ioc] -> ShowS #

Generic (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Associated Types

type Rep (BitSet1 i ioc) :: Type -> Type #

Methods

from :: BitSet1 i ioc -> Rep (BitSet1 i ioc) x #

to :: Rep (BitSet1 i ioc) x -> BitSet1 i ioc #

Arbitrary (BitSet1 t ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

arbitrary :: Gen (BitSet1 t ioc) #

shrink :: BitSet1 t ioc -> [BitSet1 t ioc] #

Unbox (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

IndexStream (Z :. BitSet1 i t) => IndexStream (BitSet1 i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (BitSet1 i t) -> LimitType (BitSet1 i t) -> Stream m (BitSet1 i t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (BitSet1 i t) -> LimitType (BitSet1 i t) -> Stream m (BitSet1 i t) Source #

Index (BitSet1 bnd ioc) Source #

NOTE We linearize a bitset as follows: we need 2^number-of-bits * number-of-bits elements. The first is due to having a binary set structure. The second is due to pointing to each of those elements as being the boundary. This overcommits on memory since only those bits can be a boundary bits that are actually set. Furthermore, in case no bit is set at all, then there should be no boundary. This is currently rather awkwardly done by restricting enumeration and mapping the 0-set to boundary 0.

| TODO The size calculations are off by a factor of two, exactly. Each bitset (say) 00110 has a mirror image 11001, whose elements do not have to be indexed. It has to be investigated if a version with exact memory bounds is slower in indexing.

Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Associated Types

data LimitType (BitSet1 bnd ioc) Source #

Methods

linearIndex :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Int Source #

fromLinearIndex :: LimitType (BitSet1 bnd ioc) -> Int -> BitSet1 bnd ioc Source #

size :: LimitType (BitSet1 bnd ioc) -> Int Source #

inBounds :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Bool Source #

zeroBound :: BitSet1 bnd ioc Source #

zeroBound' :: LimitType (BitSet1 bnd ioc) Source #

totalSize :: LimitType (BitSet1 bnd ioc) -> [Integer] Source #

showBound :: LimitType (BitSet1 bnd ioc) -> [String] Source #

showIndex :: BitSet1 bnd ioc -> [String] 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 #

newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
type Rep (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

type Rep (BitSet1 i ioc) = D1 ('MetaData "BitSet1" "Data.PrimitiveArray.Index.BitSet1" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "BitSet1" 'PrefixI 'True) (S1 ('MetaSel ('Just "_bitset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet ioc)) :*: S1 ('MetaSel ('Just "_boundary") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Boundary i ioc))))
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

boundary :: forall k (i :: k) k (ioc :: k) k (i :: k). Lens (BitSet1 (i :: k) (ioc :: k)) (BitSet1 (i :: k) (ioc :: k)) (Boundary i ioc) (Boundary i ioc) Source #

bitset :: forall k (i :: k) k (ioc :: k). Lens' (BitSet1 (i :: k) (ioc :: k)) (BitSet ioc) Source #

streamUpMk :: Monad m => Int -> Int -> z -> m (z, Maybe (BitSet1 c ioc)) Source #

streamUpStep :: Monad m => Int -> Int -> (t, Maybe (BitSet1 c ioc)) -> m (Step (t, Maybe (BitSet1 c ioc)) (t :. BitSet1 c ioc)) Source #

streamDownMk :: Monad m => Int -> Int -> z -> m (z, Maybe (BitSet1 c ioc)) Source #

streamDownStep :: Monad m => Int -> Int -> (t, Maybe (BitSet1 c ioc)) -> m (Step (t, Maybe (BitSet1 c ioc)) (t :. BitSet1 c ioc)) Source #