PrimitiveArray-0.8.0.1: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.EdgeBoundary

Description

Edge boundaries capture edge indexing of the type From :-> To, where both From and To are Ints. Each such Int gives one of the two nodes between edge exists.

Synopsis

Documentation

data EdgeBoundary t Source #

An edge boundary as two Ints denoting the edge From :-> To.

Constructors

!Int :-> !Int 

Instances

Monad m => Serial m (EdgeBoundary t) Source #

TODO this is unbelievably slow right now

Methods

series :: Series m (EdgeBoundary t) #

Vector Vector (EdgeBoundary t0) Source # 
MVector MVector (EdgeBoundary t0) Source # 
Eq (EdgeBoundary t) Source # 
Ord (EdgeBoundary t) Source # 
Read (EdgeBoundary t) Source # 
Show (EdgeBoundary t) Source # 
Generic (EdgeBoundary t) Source # 

Associated Types

type Rep (EdgeBoundary t) :: * -> * #

Methods

from :: EdgeBoundary t -> Rep (EdgeBoundary t) x #

to :: Rep (EdgeBoundary t) x -> EdgeBoundary t #

Arbitrary (EdgeBoundary t) Source # 
Hashable (EdgeBoundary t) Source # 
ToJSON (EdgeBoundary t) Source # 
ToJSONKey (EdgeBoundary t) Source # 
FromJSON (EdgeBoundary t) Source # 
FromJSONKey (EdgeBoundary t) Source # 
Binary (EdgeBoundary t) Source # 

Methods

put :: EdgeBoundary t -> Put #

get :: Get (EdgeBoundary t) #

putList :: [EdgeBoundary t] -> Put #

Serialize (EdgeBoundary t) Source # 
NFData (EdgeBoundary t) Source # 

Methods

rnf :: EdgeBoundary t -> () #

Unbox (EdgeBoundary t0) Source # 
IndexStream ((:.) Z (EdgeBoundary t)) => IndexStream (EdgeBoundary t) Source # 
Index (EdgeBoundary t) Source # 
IndexStream z => IndexStream ((:.) z (EdgeBoundary C)) Source #

EdgeBoundary C (complement)

IndexStream z => IndexStream ((:.) z (EdgeBoundary O)) Source #

EdgeBoundary O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

IndexStream z => IndexStream ((:.) z (EdgeBoundary I)) Source #

EdgeBoundary I (inside)

data MVector s (EdgeBoundary t0) Source # 
type Rep (EdgeBoundary t) Source # 
type Rep (EdgeBoundary t) = D1 (MetaData "EdgeBoundary" "Data.PrimitiveArray.Index.EdgeBoundary" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons ":->" (InfixI LeftAssociative 9) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))))
data Vector (EdgeBoundary t0) Source # 

streamUpMk :: Monad m => t1 -> t -> m (t, t1, t1) Source #

generic mk for streamUp / streamDown

streamUpStep :: Monad m => Int -> Int -> (t1, Int, Int) -> m (Step (t1, Int, Int) ((:.) t1 (EdgeBoundary t))) Source #

streamDownMk :: Monad m => t1 -> t -> m (t, t1, t1) Source #

streamDownStep :: Monad m => Int -> Int -> (t1, Int, Int) -> m (Step (t1, Int, Int) ((:.) t1 (EdgeBoundary t))) Source #