ADPfusion-0.6.0.0: Efficient, high-level dynamic programming.

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.Core.Term.Edge

Synopsis

Documentation

newtype From Source #

Constructors

From 

Fields

Instances
Eq From Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

(==) :: From -> From -> Bool #

(/=) :: From -> From -> Bool #

Ord From Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

compare :: From -> From -> Ordering #

(<) :: From -> From -> Bool #

(<=) :: From -> From -> Bool #

(>) :: From -> From -> Bool #

(>=) :: From -> From -> Bool #

max :: From -> From -> From #

min :: From -> From -> From #

Show From Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

showsPrec :: Int -> From -> ShowS #

show :: From -> String #

showList :: [From] -> ShowS #

newtype To Source #

Constructors

To 

Fields

Instances
Eq To Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

(==) :: To -> To -> Bool #

(/=) :: To -> To -> Bool #

Ord To Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

compare :: To -> To -> Ordering #

(<) :: To -> To -> Bool #

(<=) :: To -> To -> Bool #

(>) :: To -> To -> Bool #

(>=) :: To -> To -> Bool #

max :: To -> To -> To #

min :: To -> To -> To #

Show To Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

showsPrec :: Int -> To -> ShowS #

show :: To -> String #

showList :: [To] -> ShowS #

data Edge Source #

An edge in a graph. As a parsing symbol, it will provide (From:.To) pairs.

Constructors

Edge 
Instances
Build Edge Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Associated Types

type Stack Edge :: Type Source #

Methods

build :: Edge -> Stack Edge Source #

(Show i, Show (RunningIndex i), Show (Elm ls i)) => Show (Elm (ls :!: Edge) i) Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Methods

showsPrec :: Int -> Elm (ls :!: Edge) i -> ShowS #

show :: Elm (ls :!: Edge) i -> String #

showList :: [Elm (ls :!: Edge) i] -> ShowS #

Element ls i => Element (ls :!: Edge) i Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

Associated Types

data Elm (ls :!: Edge) i :: Type Source #

type RecElm (ls :!: Edge) i :: Type Source #

type Arg (ls :!: Edge) :: Type Source #

Methods

getArg :: Elm (ls :!: Edge) i -> Arg (ls :!: Edge) Source #

getIdx :: Elm (ls :!: Edge) i -> RunningIndex i Source #

getElm :: Elm (ls :!: Edge) i -> RecElm (ls :!: Edge) i Source #

type Stack Edge Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

type TermArg Edge Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

data Elm (ls :!: Edge) i Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

data Elm (ls :!: Edge) i = ElmEdge !(From :. To) !(RunningIndex i) !(Elm ls i)
type Arg (ls :!: Edge) Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Edge

type Arg (ls :!: Edge) = Arg ls :. (From :. To)

class EdgeFromTo k where Source #

edgeFromTo creates a (From:.To) structure for edges. How this is filled depends on the Proxy. Possible are Proxy First and Proxy Last. First denotes that To is the first node to be visited. I.e. First(From) → Set(To). Last on the other hand is Set(From) → Last(To).

Instances
EdgeFromTo First Source #

In case our sets have a First boundary, then we always point from the boundary "into" the set. Hence SetNode == To and NewNode == From.

{1,2,(3)} <- (4) yields From 4 :. To 3. Note the arrow direction INTO the set.

Instance details

Defined in ADP.Fusion.Core.Term.Edge

EdgeFromTo Last Source #

And if the set has a Last boundary, then we point from somewhere in the set To the NewNode, which is Last.

{1,2,(3)} -> (4) yields From 3 :. To 4. Note the arrow direction OUT OF the set.

Instance details

Defined in ADP.Fusion.Core.Term.Edge

newtype SetBoundary Source #

Constructors

SetBoundary Int 

newtype NewBoundary Source #

Constructors

NewBoundary Int