stacked-dag-0.1.1.0: Ascii DAG(Directed acyclic graph) for visualization of dataflow

Safe HaskellSafe
LanguageHaskell2010

StackedDag.Base

Synopsis

Documentation

type Edges a = Map a (Set a) Source #

type Labels a b = Map a b Source #

data Symbol b Source #

Constructors

SNode b 
SLeft 
SRight 
SHold 
SLMove 
SRMove 
SCross 
SSpace 
Instances
Eq b => Eq (Symbol b) Source # 
Instance details

Defined in StackedDag.Base

Methods

(==) :: Symbol b -> Symbol b -> Bool #

(/=) :: Symbol b -> Symbol b -> Bool #

Read b => Read (Symbol b) Source # 
Instance details

Defined in StackedDag.Base

Show b => Show (Symbol b) Source # 
Instance details

Defined in StackedDag.Base

Methods

showsPrec :: Int -> Symbol b -> ShowS #

show :: Symbol b -> String #

showList :: [Symbol b] -> ShowS #

Semigroup (Symbol b) Source # 
Instance details

Defined in StackedDag.Base

Methods

(<>) :: Symbol b -> Symbol b -> Symbol b #

sconcat :: NonEmpty (Symbol b) -> Symbol b #

stimes :: Integral b0 => b0 -> Symbol b -> Symbol b #

Monoid (Symbol b) Source # 
Instance details

Defined in StackedDag.Base

Methods

mempty :: Symbol b #

mappend :: Symbol b -> Symbol b -> Symbol b #

mconcat :: [Symbol b] -> Symbol b #

type Nodes a = Set a Source #

type Depth = Int Source #

type Dest = Int Source #

type Cur = Int Source #

type Pos = Int Source #

type DepthGroup a = Map Depth [a] Source #

type DepthGroup' a = Map Depth ([a], [a]) Source #

type DepthGroup'' a = Map Depth ([(a, Cur, Dest)], [(a, Cur, Dest)]) Source #

mkEdges :: Ord a => [(a, [a])] -> Edges a Source #

mkLabels :: Ord a => [(a, b)] -> Labels a b Source #

getDepthGroup :: forall a. Ord a => Edges a -> DepthGroup a Source #

Grouping the nodes by the depth

>>> getDepthGroup sampledat
fromList [(0,[5]),(1,[3]),(2,[2,4,6]),(3,[0,1])]

getDepthGroup2 :: forall a b. (Ord a, Ord b) => Labels a b -> Edges a -> DepthGroup a Source #

Grouping the nodes by the depth

>>> getDepthGroup2 samplelabels sampledat
fromList [(0,[5]),(1,[3]),(2,[2,4,6]),(3,[0,1])]

pairs :: Map b (Set a) -> [(a, b)] Source #

reverseEdges :: Ord a => Edges a -> Edges a Source #

Reverse the directions of edges

>>> sampledat
fromList [(0,fromList [2]),(1,fromList [2]),(2,fromList [3]),(3,fromList [5]),(4,fromList [3]),(6,fromList [3])]
>>> reverseEdges sampledat
fromList [(2,fromList [0,1]),(3,fromList [2,4,6]),(5,fromList [3])]

getNodes :: Ord a => Edges a -> Nodes a Source #

Get nodes by edges

>>> getNodes sampledat
fromList [0,1,2,3,4,5,6]

getDepth2 :: forall a. Ord a => Edges a -> DepthNode a Source #

Find all depth of nodes. This is faster than getDepth.

getDepth :: forall a. Ord a => Edges a -> DepthNode a Source #

Find all depth of nodes

moveOne :: Ord a => [(a, Cur, Dest)] -> [((a, Cur, Dest), [(Symbol b, Pos)])] Source #

Move nodes to next step

>>> moveOne [(0,0,4)]
[((0,2,4),[(SRight,1)])]
>>> moveOne [(0,0,4),(0,4,0)]
[((0,2,4),[(SRight,1)]),((0,2,0),[(SLeft,3)])]

takeNode :: Ord a => Cur -> [((a, Cur, Dest), [(Symbol b, Pos)])] -> Maybe ((a, Cur, Dest), [(Symbol b, Pos)]) Source #

moveLeft' :: Ord a => [((a, Cur, Dest), [(Symbol b, Pos)])] -> [((a, Cur, Dest), [(Symbol b, Pos)])] Source #

Move more nodes

>>> moveLeft' [((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,2,0),[(SLeft,3)])]
[((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,0,0),[(SLMove,2),(SLeft,3)])]
>>> moveLeft' [((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,0,0),[(SLMove,2),(SLeft,3)]),((3,2,0),[(SLMove,4),(SLeft,5)])]
[((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,0,0),[(SLMove,2),(SLeft,3)]),((3,0,0),[(SLMove,4),(SLeft,5)])]
>>> moveLeft' [((0,2,0),[(SLeft,3)])]
[((0,0,0),[(SLMove,1),(SLMove,2),(SLeft,3)])]

moveLeft :: (Ord a, Eq b) => [((a, Cur, Dest), [(Symbol b, Pos)])] -> [((a, Cur, Dest), [(Symbol b, Pos)])] Source #

Move more nodes

>>> moveLeft [((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,2,0),[(SLeft,3)]),((3,4,0),[(SLeft,5)])]
[((0,0,0),[(SHold,0)]),((1,0,0),[(SLeft,1)]),((2,0,0),[(SLMove,2),(SLeft,3)]),((3,0,0),[(SLMove,4),(SLeft,5)])]

moveAll' :: (Ord a, Eq b) => [(a, Cur, Dest)] -> [[(Symbol b, Pos)]] -> [[(Symbol b, Pos)]] Source #

Move nodes to the next depth

>>> moveAll' [(0,0,4)] []
[[(SRight,1)],[(SRight,3)]]
>>> moveAll' [(0,4,0)] []
[[(SLMove,1),(SLMove,2),(SLeft,3)]]
>>> moveAll' [(0,2,0)] []
[[(SLeft,1)]]
>>> moveAll' [(0,0,4),(0,4,0)] []
[[(SRight,1),(SLeft,3)],[(SRight,3),(SLeft,1)]]
>>> moveAll' [(0,0,4),(0,2,0)] []
[[(SRight,1),(SLeft,1)],[(SRight,3),(SHold,0)]]

mergeSymbol :: [(Symbol b, Pos)] -> [(Symbol b, Pos)] Source #

withSpace :: [(Symbol b, Pos)] -> [Symbol b] Source #

Fill spaces

>>> withSpace [(SRight,1),(SLeft,3)]
[SSpace,SRight,SSpace,SLeft]
>>> withSpace [(SRight,3),(SLeft,1)]
[SSpace,SLeft,SSpace,SRight]

moveAllWithSpace :: (Ord a, Eq b) => [(a, Cur, Dest)] -> [[Symbol b]] Source #

Move nodes and fill spaces

>>> moveAllWithSpace [(0,0,4)]
[[SSpace,SRight],[SSpace,SSpace,SSpace,SRight]]
>>> moveAllWithSpace [(0,4,0)]
[[SSpace,SLMove,SLMove,SLeft]]
>>> moveAllWithSpace [(0,0,4),(0,4,0)]
[[SSpace,SRight,SSpace,SLeft],[SSpace,SLeft,SSpace,SRight]]
>>> moveAllWithSpace [(0,4,0),(1,0,4)]
[[SSpace,SRight,SSpace,SLeft],[SSpace,SLeft,SSpace,SRight]]

lstr :: (Ord a, Monoid b) => Labels a b -> a -> b Source #

nodeWithSpace :: (Ord a, Monoid b) => Labels a b -> ([(a, Cur, Dest)], [(a, Cur, Dest)]) -> [Symbol b] Source #

addBypassNode'' :: forall a. Ord a => Depth -> Edges a -> NodeDepth a -> DepthGroup' a -> DepthGroup' a Source #

Add bypass nodes

>>> let edges = mkEdges [(0,[1,2]),(1,[2])]
>>> let nd = getNodeDepth $ getDepthGroup edges
>>> addBypassNode'' 2 edges nd (M.fromList [(0,([2],[])),(1,([1],[])),(2,([0],[]))])
fromList [(0,([2],[])),(1,([1],[0])),(2,([0],[]))]
>>> let edges = mkEdges [(0,[1,3]),(1,[2]),(2,[3])]
>>> let nd = getNodeDepth $ getDepthGroup edges
>>> addBypassNode'' 3 edges nd (M.fromList [(0,([3],[])),(1,([2],[])),(2,([1],[])),(3,([0],[]))])
fromList [(0,([3],[])),(1,([2],[])),(2,([1],[0])),(3,([0],[]))]
>>> addBypassNode'' 2 edges nd (M.fromList [(0,([3],[])),(1,([2],[])),(2,([1],[0])),(3,([0],[]))])
fromList [(0,([3],[])),(1,([2],[0])),(2,([1],[0])),(3,([0],[]))]
>>> let edges = mkEdges [(0,[1,2]),(1,[4]),(2,[3]),(3,[4])]
>>> let nd = getNodeDepth $ getDepthGroup edges
>>> addBypassNode'' 2 edges nd (M.fromList [(0,([4],[])),(1,([3,1],[])),(2,([2],[0])),(3,([0],[]))])
fromList [(0,([4],[])),(1,([3,1],[])),(2,([2],[0])),(3,([0],[]))]

maxDepth :: Ord a => DepthGroup' a -> Int Source #

Get a maximum of depth

>>> maxDepth (M.fromList [(0,([2],[])),(1,([1],[])),(2,([0],[]))])
2

addBypassNode' :: Ord a => Edges a -> NodeDepth a -> DepthGroup' a -> DepthGroup' a Source #

Add bypass nodes

>>> let edges = mkEdges [(0,[1,2]),(1,[2])]
>>> let nd = getNodeDepth $ getDepthGroup edges
>>> addBypassNode' edges nd (M.fromList [(0,([2],[])),(1,([1],[])),(2,([0],[]))])
fromList [(0,([2],[])),(1,([1],[0])),(2,([0],[]))]
>>> let edges = mkEdges [(0,[1,3]),(1,[2]),(2,[3])]
>>> let nd = getNodeDepth $ getDepthGroup edges
>>> addBypassNode' edges nd (M.fromList [(0,([3],[])),(1,([2],[])),(2,([1],[])),(3,([0],[]))])
fromList [(0,([3],[])),(1,([2],[0])),(2,([1],[0])),(3,([0],[]))]

addBypassNode :: Ord a => Edges a -> NodeDepth a -> DepthGroup a -> DepthGroup' a Source #

Add bypass nodes

>>> let edges = mkEdges [(0,[1,2]),(1,[2])]
>>> let dg = getDepthGroup edges
>>> let nd = getNodeDepth dg
>>> addBypassNode edges nd dg
fromList [(0,([2],[])),(1,([1],[0])),(2,([0],[]))]
>>> let edges = mkEdges [(0,[1,3]),(1,[2]),(2,[3])]
>>> let dg = getDepthGroup edges
>>> let nd = getNodeDepth dg
>>> addBypassNode edges nd dg
fromList [(0,([3],[])),(1,([2],[0])),(2,([1],[0])),(3,([0],[]))]
>>> let edges = mkEdges [(0,[1,2]),(1,[4]),(2,[3]),(3,[4])]
>>> let dg = getDepthGroup edges
>>> let nd = getNodeDepth dg
>>> addBypassNode edges nd dg
fromList [(0,([4],[])),(1,([3,1],[])),(2,([2],[0])),(3,([0],[]))]

addDestWithBypass :: forall a. Ord a => Edges a -> DepthGroup' a -> DepthGroup'' a Source #

Add destinations of nodes

>>> let edges = mkEdges [(0,[1,2]),(1,[2])]
>>> let dg = getDepthGroup edges
>>> addDestWithBypass edges $ M.fromList [(0,([2],[])),(1,([1],[0])),(2,([0],[]))]
fromList [(0,([(2,0,0)],[])),(1,([(1,0,0)],[(0,2,0)])),(2,([(0,0,0),(0,0,2)],[]))]

addNode :: Ord a => Edges a -> NodeDepth a -> DepthGroup a -> DepthGroup'' a Source #

Grouping the nodes by the depth

>>> let edges = mkEdges [(0,[1,2])]
>>> let dg = getDepthGroup edges
>>> let nd = getNodeDepth dg
>>> dg
fromList [(0,[1,2]),(1,[0])]
>>> addNode edges nd dg
fromList [(0,([(1,0,0),(2,2,2)],[])),(1,([(0,0,0),(0,0,2)],[]))]

toSymbol :: (Ord a, Eq b, Monoid b) => Labels a b -> DepthGroup'' a -> [[Symbol b]] Source #

renderToText :: [[Symbol String]] -> [String] -> String Source #

Rendering symbols to text

>>> renderToText [[SNode ""],[SHold],[SNode ""]] []
"o\n|\no\n"
>>> renderToText [[SNode "",SSpace,SNode ""],[SHold,SLeft],[SNode ""]] []
"o o\n|/\no\n"

addDest :: Ord a => Edges a -> ([a], [a]) -> ([a], [a]) -> ([(a, Cur, Dest)], [(a, Cur, Dest)]) Source #

Allocate destinations of nodes.

>>> addDest sampledat ([0,1],[]) ([2],[])
([(0,0,0),(1,2,0)],[])
>>> addDest (mkEdges [(0,[1,2]),(1,[2])]) ([0],[]) ([1],[0])
([(0,0,0),(0,0,2)],[])
>>> addDest (mkEdges [(0,[1,2]),(1,[2])]) ([1],[0]) ([2],[])
([(1,0,0)],[(0,2,0)])
>>> addDest (mkEdges [(0,[1,3]),(1,[2]),(2,[3])]) ([1],[0]) ([2],[0])
([(1,0,0)],[(0,2,2)])