{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses,
TypeSynonymInstances #-}
module Data.GraphViz.Types
( DotRepr(..)
, PrintDot(..)
, ParseDot(..)
, PrintDotRepr
, ParseDotRepr
, PPDotRepr
, GraphID(..)
, Number (..)
, ToGraphID(..)
, textGraphID
, GlobalAttributes(..)
, DotNode(..)
, DotEdge(..)
, ClusterLookup
, NodeLookup
, Path
, graphStructureInformationClean
, nodeInformationClean
, edgeInformationClean
, graphNodes
, graphEdges
, printDotGraph
, parseDotGraph
, parseDotGraphLiberally
) where
import Data.GraphViz.Attributes.Complete (rmUnwantedAttributes,
usedByClusters, usedByEdges,
usedByGraphs, usedByNodes)
import Data.GraphViz.Internal.State (GraphvizState)
import Data.GraphViz.Internal.Util (bool)
import Data.GraphViz.Parsing (ParseDot(..), adjustErr,
checkValidParseWithRest, parse,
parseLiberally, runParserWith)
import Data.GraphViz.PreProcessing (preProcess)
import Data.GraphViz.Printing (PrintDot(..), printIt)
import Data.GraphViz.Types.Canonical (DotGraph(..), DotStatements(..),
DotSubGraph(..))
import Data.GraphViz.Types.Internal.Common (DotEdge(..), DotNode(..),
GlobalAttributes(..), GraphID(..),
Number(..), numericValue, withGlob)
import Data.GraphViz.Types.State
import Control.Arrow (second, (***))
import Control.Monad.State (evalState, execState, get, modify, put)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
class (Ord n) => DotRepr dg n where
fromCanonical :: DotGraph n -> dg n
getID :: dg n -> Maybe GraphID
setID :: GraphID -> dg n -> dg n
graphIsDirected :: dg n -> Bool
setIsDirected :: Bool -> dg n -> dg n
graphIsStrict :: dg n -> Bool
setStrictness :: Bool -> dg n -> dg n
mapDotGraph :: (DotRepr dg n') => (n -> n') -> dg n -> dg n'
graphStructureInformation :: dg n -> (GlobalAttributes, ClusterLookup)
nodeInformation :: Bool -> dg n -> NodeLookup n
edgeInformation :: Bool -> dg n -> [DotEdge n]
unAnonymise :: dg n -> dg n
graphStructureInformationClean :: (DotRepr dg n) => dg n
-> (GlobalAttributes, ClusterLookup)
graphStructureInformationClean :: forall (dg :: * -> *) n.
DotRepr dg n =>
dg n -> (GlobalAttributes, ClusterLookup)
graphStructureInformationClean = (GlobalAttributes -> GlobalAttributes
globOnly (GlobalAttributes -> GlobalAttributes)
-> (ClusterLookup -> ClusterLookup)
-> (GlobalAttributes, ClusterLookup)
-> (GlobalAttributes, ClusterLookup)
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (([Path], GlobalAttributes) -> ([Path], GlobalAttributes))
-> ClusterLookup -> ClusterLookup
forall a b.
(a -> b) -> Map (Maybe GraphID) a -> Map (Maybe GraphID) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((GlobalAttributes -> GlobalAttributes)
-> ([Path], GlobalAttributes) -> ([Path], GlobalAttributes)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second GlobalAttributes -> GlobalAttributes
clustOnly))
((GlobalAttributes, ClusterLookup)
-> (GlobalAttributes, ClusterLookup))
-> (dg n -> (GlobalAttributes, ClusterLookup))
-> dg n
-> (GlobalAttributes, ClusterLookup)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. dg n -> (GlobalAttributes, ClusterLookup)
forall (dg :: * -> *) n.
DotRepr dg n =>
dg n -> (GlobalAttributes, ClusterLookup)
graphStructureInformation
where
globOnly :: GlobalAttributes -> GlobalAttributes
globOnly = (Attributes -> Attributes) -> GlobalAttributes -> GlobalAttributes
withGlob ((Attributes -> Attributes)
-> GlobalAttributes -> GlobalAttributes)
-> (Attributes -> Attributes)
-> GlobalAttributes
-> GlobalAttributes
forall a b. (a -> b) -> a -> b
$ (Attribute -> Bool) -> Attributes -> Attributes
forall a. (a -> Bool) -> [a] -> [a]
filter Attribute -> Bool
usedByGraphs (Attributes -> Attributes)
-> (Attributes -> Attributes) -> Attributes -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes -> Attributes
rmUnwantedAttributes
clustOnly :: GlobalAttributes -> GlobalAttributes
clustOnly = (Attributes -> Attributes) -> GlobalAttributes -> GlobalAttributes
withGlob ((Attributes -> Attributes)
-> GlobalAttributes -> GlobalAttributes)
-> (Attributes -> Attributes)
-> GlobalAttributes
-> GlobalAttributes
forall a b. (a -> b) -> a -> b
$ (Attribute -> Bool) -> Attributes -> Attributes
forall a. (a -> Bool) -> [a] -> [a]
filter Attribute -> Bool
usedByClusters (Attributes -> Attributes)
-> (Attributes -> Attributes) -> Attributes -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes -> Attributes
rmUnwantedAttributes
nodeInformationClean :: (DotRepr dg n) => Bool -> dg n -> NodeLookup n
nodeInformationClean :: forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> NodeLookup n
nodeInformationClean = (((Path, Attributes) -> (Path, Attributes))
-> Map n (Path, Attributes) -> Map n (Path, Attributes)
forall a b. (a -> b) -> Map n a -> Map n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Attributes -> Attributes)
-> (Path, Attributes) -> (Path, Attributes)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Attributes -> Attributes
nodeOnly) (Map n (Path, Attributes) -> Map n (Path, Attributes))
-> (dg n -> Map n (Path, Attributes))
-> dg n
-> Map n (Path, Attributes)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((dg n -> Map n (Path, Attributes))
-> dg n -> Map n (Path, Attributes))
-> (Bool -> dg n -> Map n (Path, Attributes))
-> Bool
-> dg n
-> Map n (Path, Attributes)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> dg n -> Map n (Path, Attributes)
forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> NodeLookup n
nodeInformation
where
nodeOnly :: Attributes -> Attributes
nodeOnly = (Attribute -> Bool) -> Attributes -> Attributes
forall a. (a -> Bool) -> [a] -> [a]
filter Attribute -> Bool
usedByNodes (Attributes -> Attributes)
-> (Attributes -> Attributes) -> Attributes -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes -> Attributes
rmUnwantedAttributes
edgeInformationClean :: (DotRepr dg n) => Bool -> dg n -> [DotEdge n]
edgeInformationClean :: forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> [DotEdge n]
edgeInformationClean = ((DotEdge n -> DotEdge n) -> [DotEdge n] -> [DotEdge n]
forall a b. (a -> b) -> [a] -> [b]
map DotEdge n -> DotEdge n
forall {n}. DotEdge n -> DotEdge n
rmEdgeAs ([DotEdge n] -> [DotEdge n])
-> (dg n -> [DotEdge n]) -> dg n -> [DotEdge n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((dg n -> [DotEdge n]) -> dg n -> [DotEdge n])
-> (Bool -> dg n -> [DotEdge n]) -> Bool -> dg n -> [DotEdge n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> dg n -> [DotEdge n]
forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> [DotEdge n]
edgeInformation
where
rmEdgeAs :: DotEdge n -> DotEdge n
rmEdgeAs DotEdge n
de = DotEdge n
de { edgeAttributes = edgeOnly $ edgeAttributes de }
edgeOnly :: Attributes -> Attributes
edgeOnly = (Attribute -> Bool) -> Attributes -> Attributes
forall a. (a -> Bool) -> [a] -> [a]
filter Attribute -> Bool
usedByEdges (Attributes -> Attributes)
-> (Attributes -> Attributes) -> Attributes -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes -> Attributes
rmUnwantedAttributes
class (DotRepr dg n, PrintDot (dg n)) => PrintDotRepr dg n
class (DotRepr dg n, ParseDot (dg n)) => ParseDotRepr dg n
class (PrintDotRepr dg n, ParseDotRepr dg n) => PPDotRepr dg n
graphNodes :: (DotRepr dg n) => dg n -> [DotNode n]
graphNodes :: forall (dg :: * -> *) n. DotRepr dg n => dg n -> [DotNode n]
graphNodes = NodeLookup n -> [DotNode n]
forall n. NodeLookup n -> [DotNode n]
toDotNodes (NodeLookup n -> [DotNode n])
-> (dg n -> NodeLookup n) -> dg n -> [DotNode n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> dg n -> NodeLookup n
forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> NodeLookup n
nodeInformation Bool
False
graphEdges :: (DotRepr dg n) => dg n -> [DotEdge n]
graphEdges :: forall (dg :: * -> *) n. DotRepr dg n => dg n -> [DotEdge n]
graphEdges = Bool -> dg n -> [DotEdge n]
forall (dg :: * -> *) n.
DotRepr dg n =>
Bool -> dg n -> [DotEdge n]
edgeInformation Bool
False
printDotGraph :: (PrintDotRepr dg n) => dg n -> Text
printDotGraph :: forall (dg :: * -> *) n. PrintDotRepr dg n => dg n -> Text
printDotGraph = dg n -> Text
forall a. PrintDot a => a -> Text
printIt
parseDotGraph :: (ParseDotRepr dg n) => Text -> dg n
parseDotGraph :: forall (dg :: * -> *) n. ParseDotRepr dg n => Text -> dg n
parseDotGraph = (GraphvizState -> GraphvizState) -> Text -> dg n
forall (dg :: * -> *) n.
ParseDotRepr dg n =>
(GraphvizState -> GraphvizState) -> Text -> dg n
parseDotGraphWith GraphvizState -> GraphvizState
forall a. a -> a
id
parseDotGraphLiberally :: (ParseDotRepr dg n) => Text -> dg n
parseDotGraphLiberally :: forall (dg :: * -> *) n. ParseDotRepr dg n => Text -> dg n
parseDotGraphLiberally = (GraphvizState -> GraphvizState) -> Text -> dg n
forall (dg :: * -> *) n.
ParseDotRepr dg n =>
(GraphvizState -> GraphvizState) -> Text -> dg n
parseDotGraphWith GraphvizState -> GraphvizState
parseLiberally
parseDotGraphWith :: (ParseDotRepr dg n) => (GraphvizState -> GraphvizState)
-> Text -> dg n
parseDotGraphWith :: forall (dg :: * -> *) n.
ParseDotRepr dg n =>
(GraphvizState -> GraphvizState) -> Text -> dg n
parseDotGraphWith GraphvizState -> GraphvizState
f = Text -> dg n
prs (Text -> dg n) -> (Text -> Text) -> Text -> dg n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
preProcess
where
prs :: Text -> dg n
prs = (Either String (dg n), Text) -> dg n
forall a. (Either String a, Text) -> a
checkValidParseWithRest ((Either String (dg n), Text) -> dg n)
-> (Text -> (Either String (dg n), Text)) -> Text -> dg n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GraphvizState -> GraphvizState)
-> Parse (dg n) -> Text -> (Either String (dg n), Text)
forall a.
(GraphvizState -> GraphvizState)
-> Parse a -> Text -> (Either String a, Text)
runParserWith GraphvizState -> GraphvizState
f Parse (dg n)
parse'
parse' :: Parse (dg n)
parse' = Parse (dg n)
forall a. ParseDot a => Parse a
parse Parse (dg n) -> (String -> String) -> Parse (dg n)
forall a.
Parser GraphvizState a
-> (String -> String) -> Parser GraphvizState a
forall (p :: * -> *) a.
Commitment p =>
p a -> (String -> String) -> p a
`adjustErr`
(String
"Unable to parse the Dot graph; usually this is because of either:\n\
\ * Wrong choice of representation: try the Generalised one\n\
\ * Wrong choice of node type; try with `DotGraph String`.\n\
\\n\
\The actual parsing error was:\n\t"String -> String -> String
forall a. [a] -> [a] -> [a]
++)
instance (Ord n) => DotRepr DotGraph n where
fromCanonical :: DotGraph n -> DotGraph n
fromCanonical = DotGraph n -> DotGraph n
forall a. a -> a
id
getID :: DotGraph n -> Maybe GraphID
getID = DotGraph n -> Maybe GraphID
forall n. DotGraph n -> Maybe GraphID
graphID
setID :: GraphID -> DotGraph n -> DotGraph n
setID GraphID
i DotGraph n
g = DotGraph n
g { graphID = Just i }
graphIsDirected :: DotGraph n -> Bool
graphIsDirected = DotGraph n -> Bool
forall n. DotGraph n -> Bool
directedGraph
setIsDirected :: Bool -> DotGraph n -> DotGraph n
setIsDirected Bool
d DotGraph n
g = DotGraph n
g { directedGraph = d }
graphIsStrict :: DotGraph n -> Bool
graphIsStrict = DotGraph n -> Bool
forall n. DotGraph n -> Bool
strictGraph
setStrictness :: Bool -> DotGraph n -> DotGraph n
setStrictness Bool
s DotGraph n
g = DotGraph n
g { strictGraph = s }
mapDotGraph :: forall n'.
DotRepr DotGraph n' =>
(n -> n') -> DotGraph n -> DotGraph n'
mapDotGraph = (n -> n') -> DotGraph n -> DotGraph n'
forall a b. (a -> b) -> DotGraph a -> DotGraph b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
graphStructureInformation :: DotGraph n -> (GlobalAttributes, ClusterLookup)
graphStructureInformation = GraphState () -> (GlobalAttributes, ClusterLookup)
forall a. GraphState a -> (GlobalAttributes, ClusterLookup)
getGraphInfo
(GraphState () -> (GlobalAttributes, ClusterLookup))
-> (DotGraph n -> GraphState ())
-> DotGraph n
-> (GlobalAttributes, ClusterLookup)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotStatements n -> GraphState ()
forall n. DotStatements n -> GraphState ()
statementStructure (DotStatements n -> GraphState ())
-> (DotGraph n -> DotStatements n) -> DotGraph n -> GraphState ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotGraph n -> DotStatements n
forall n. DotGraph n -> DotStatements n
graphStatements
nodeInformation :: Bool -> DotGraph n -> NodeLookup n
nodeInformation Bool
wGlobal = Bool -> NodeState n () -> NodeLookup n
forall n a. Bool -> NodeState n a -> NodeLookup n
getNodeLookup Bool
wGlobal
(NodeState n () -> NodeLookup n)
-> (DotGraph n -> NodeState n ()) -> DotGraph n -> NodeLookup n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotStatements n -> NodeState n ()
forall n. Ord n => DotStatements n -> NodeState n ()
statementNodes (DotStatements n -> NodeState n ())
-> (DotGraph n -> DotStatements n) -> DotGraph n -> NodeState n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotGraph n -> DotStatements n
forall n. DotGraph n -> DotStatements n
graphStatements
edgeInformation :: Bool -> DotGraph n -> [DotEdge n]
edgeInformation Bool
wGlobal = Bool -> EdgeState n () -> [DotEdge n]
forall n a. Bool -> EdgeState n a -> [DotEdge n]
getDotEdges Bool
wGlobal
(EdgeState n () -> [DotEdge n])
-> (DotGraph n -> EdgeState n ()) -> DotGraph n -> [DotEdge n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotStatements n -> EdgeState n ()
forall n. DotStatements n -> EdgeState n ()
statementEdges (DotStatements n -> EdgeState n ())
-> (DotGraph n -> DotStatements n) -> DotGraph n -> EdgeState n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotGraph n -> DotStatements n
forall n. DotGraph n -> DotStatements n
graphStatements
unAnonymise :: DotGraph n -> DotGraph n
unAnonymise = DotGraph n -> DotGraph n
forall n. DotGraph n -> DotGraph n
renumber
instance (Ord n, PrintDot n) => PrintDotRepr DotGraph n
instance (Ord n, ParseDot n) => ParseDotRepr DotGraph n
instance (Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n
statementStructure :: DotStatements n -> GraphState ()
statementStructure :: forall n. DotStatements n -> GraphState ()
statementStructure DotStatements n
stmts
= do (GlobalAttributes -> GraphState ())
-> [GlobalAttributes] -> GraphState ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GlobalAttributes -> GraphState ()
addGraphGlobals ([GlobalAttributes] -> GraphState ())
-> [GlobalAttributes] -> GraphState ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [GlobalAttributes]
forall n. DotStatements n -> [GlobalAttributes]
attrStmts DotStatements n
stmts
(DotSubGraph n -> GraphState ())
-> [DotSubGraph n] -> GraphState ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((Maybe (Maybe GraphID) -> GraphState () -> GraphState ())
-> (DotStatements n -> GraphState ())
-> DotSubGraph n
-> GraphState ()
forall b a n.
(Maybe (Maybe GraphID) -> b -> a)
-> (DotStatements n -> b) -> DotSubGraph n -> a
withSubGraphID Maybe (Maybe GraphID) -> GraphState () -> GraphState ()
forall a. Maybe (Maybe GraphID) -> GraphState a -> GraphState ()
addSubGraph DotStatements n -> GraphState ()
forall n. DotStatements n -> GraphState ()
statementStructure) ([DotSubGraph n] -> GraphState ())
-> [DotSubGraph n] -> GraphState ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotSubGraph n]
forall n. DotStatements n -> [DotSubGraph n]
subGraphs DotStatements n
stmts
statementNodes :: (Ord n) => DotStatements n -> NodeState n ()
statementNodes :: forall n. Ord n => DotStatements n -> NodeState n ()
statementNodes DotStatements n
stmts
= do (GlobalAttributes -> NodeState n ())
-> [GlobalAttributes] -> NodeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GlobalAttributes -> NodeState n ()
forall n. GlobalAttributes -> NodeState n ()
addNodeGlobals ([GlobalAttributes] -> NodeState n ())
-> [GlobalAttributes] -> NodeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [GlobalAttributes]
forall n. DotStatements n -> [GlobalAttributes]
attrStmts DotStatements n
stmts
(DotSubGraph n -> NodeState n ())
-> [DotSubGraph n] -> NodeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((Maybe (Maybe GraphID) -> NodeState n () -> NodeState n ())
-> (DotStatements n -> NodeState n ())
-> DotSubGraph n
-> NodeState n ()
forall b a n.
(Maybe (Maybe GraphID) -> b -> a)
-> (DotStatements n -> b) -> DotSubGraph n -> a
withSubGraphID Maybe (Maybe GraphID) -> NodeState n () -> NodeState n ()
forall s. Maybe (Maybe GraphID) -> GVState s () -> GVState s ()
recursiveCall DotStatements n -> NodeState n ()
forall n. Ord n => DotStatements n -> NodeState n ()
statementNodes) ([DotSubGraph n] -> NodeState n ())
-> [DotSubGraph n] -> NodeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotSubGraph n]
forall n. DotStatements n -> [DotSubGraph n]
subGraphs DotStatements n
stmts
(DotNode n -> NodeState n ()) -> [DotNode n] -> NodeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DotNode n -> NodeState n ()
forall n. Ord n => DotNode n -> NodeState n ()
addNode ([DotNode n] -> NodeState n ()) -> [DotNode n] -> NodeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotNode n]
forall n. DotStatements n -> [DotNode n]
nodeStmts DotStatements n
stmts
(DotEdge n -> NodeState n ()) -> [DotEdge n] -> NodeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DotEdge n -> NodeState n ()
forall n. Ord n => DotEdge n -> NodeState n ()
addEdgeNodes ([DotEdge n] -> NodeState n ()) -> [DotEdge n] -> NodeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotEdge n]
forall n. DotStatements n -> [DotEdge n]
edgeStmts DotStatements n
stmts
statementEdges :: DotStatements n -> EdgeState n ()
statementEdges :: forall n. DotStatements n -> EdgeState n ()
statementEdges DotStatements n
stmts
= do (GlobalAttributes -> EdgeState n ())
-> [GlobalAttributes] -> EdgeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GlobalAttributes -> EdgeState n ()
forall n. GlobalAttributes -> EdgeState n ()
addEdgeGlobals ([GlobalAttributes] -> EdgeState n ())
-> [GlobalAttributes] -> EdgeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [GlobalAttributes]
forall n. DotStatements n -> [GlobalAttributes]
attrStmts DotStatements n
stmts
(DotSubGraph n -> EdgeState n ())
-> [DotSubGraph n] -> EdgeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((Maybe (Maybe GraphID) -> EdgeState n () -> EdgeState n ())
-> (DotStatements n -> EdgeState n ())
-> DotSubGraph n
-> EdgeState n ()
forall b a n.
(Maybe (Maybe GraphID) -> b -> a)
-> (DotStatements n -> b) -> DotSubGraph n -> a
withSubGraphID Maybe (Maybe GraphID) -> EdgeState n () -> EdgeState n ()
forall s. Maybe (Maybe GraphID) -> GVState s () -> GVState s ()
recursiveCall DotStatements n -> EdgeState n ()
forall n. DotStatements n -> EdgeState n ()
statementEdges) ([DotSubGraph n] -> EdgeState n ())
-> [DotSubGraph n] -> EdgeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotSubGraph n]
forall n. DotStatements n -> [DotSubGraph n]
subGraphs DotStatements n
stmts
(DotEdge n -> EdgeState n ()) -> [DotEdge n] -> EdgeState n ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DotEdge n -> EdgeState n ()
forall n. DotEdge n -> EdgeState n ()
addEdge ([DotEdge n] -> EdgeState n ()) -> [DotEdge n] -> EdgeState n ()
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotEdge n]
forall n. DotStatements n -> [DotEdge n]
edgeStmts DotStatements n
stmts
withSubGraphID :: (Maybe (Maybe GraphID) -> b -> a)
-> (DotStatements n -> b) -> DotSubGraph n -> a
withSubGraphID :: forall b a n.
(Maybe (Maybe GraphID) -> b -> a)
-> (DotStatements n -> b) -> DotSubGraph n -> a
withSubGraphID Maybe (Maybe GraphID) -> b -> a
f DotStatements n -> b
g DotSubGraph n
sg = Maybe (Maybe GraphID) -> b -> a
f Maybe (Maybe GraphID)
mid (b -> a) -> (DotStatements n -> b) -> DotStatements n -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotStatements n -> b
g (DotStatements n -> a) -> DotStatements n -> a
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> DotStatements n
forall n. DotSubGraph n -> DotStatements n
subGraphStmts DotSubGraph n
sg
where
mid :: Maybe (Maybe GraphID)
mid = Maybe (Maybe GraphID)
-> Maybe (Maybe GraphID) -> Bool -> Maybe (Maybe GraphID)
forall a. a -> a -> Bool -> a
bool Maybe (Maybe GraphID)
forall a. Maybe a
Nothing (Maybe GraphID -> Maybe (Maybe GraphID)
forall a. a -> Maybe a
Just (Maybe GraphID -> Maybe (Maybe GraphID))
-> Maybe GraphID -> Maybe (Maybe GraphID)
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> Maybe GraphID
forall n. DotSubGraph n -> Maybe GraphID
subGraphID DotSubGraph n
sg) (Bool -> Maybe (Maybe GraphID)) -> Bool -> Maybe (Maybe GraphID)
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> Bool
forall n. DotSubGraph n -> Bool
isCluster DotSubGraph n
sg
renumber :: DotGraph n -> DotGraph n
renumber :: forall n. DotGraph n -> DotGraph n
renumber DotGraph n
dg = DotGraph n
dg { graphStatements = newStmts }
where
startN :: Int
startN = Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DotGraph n -> Int
forall n. DotGraph n -> Int
maxSGInt DotGraph n
dg
newStmts :: DotStatements n
newStmts = State Int (DotStatements n) -> Int -> DotStatements n
forall s a. State s a -> s -> a
evalState (DotStatements n -> State Int (DotStatements n)
forall {m :: * -> *} {n}.
MonadState Int m =>
DotStatements n -> m (DotStatements n)
stRe (DotStatements n -> State Int (DotStatements n))
-> DotStatements n -> State Int (DotStatements n)
forall a b. (a -> b) -> a -> b
$ DotGraph n -> DotStatements n
forall n. DotGraph n -> DotStatements n
graphStatements DotGraph n
dg) Int
startN
stRe :: DotStatements n -> m (DotStatements n)
stRe DotStatements n
st = do [DotSubGraph n]
sgs' <- (DotSubGraph n -> m (DotSubGraph n))
-> [DotSubGraph n] -> m [DotSubGraph n]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM DotSubGraph n -> m (DotSubGraph n)
sgRe ([DotSubGraph n] -> m [DotSubGraph n])
-> [DotSubGraph n] -> m [DotSubGraph n]
forall a b. (a -> b) -> a -> b
$ DotStatements n -> [DotSubGraph n]
forall n. DotStatements n -> [DotSubGraph n]
subGraphs DotStatements n
st
DotStatements n -> m (DotStatements n)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (DotStatements n -> m (DotStatements n))
-> DotStatements n -> m (DotStatements n)
forall a b. (a -> b) -> a -> b
$ DotStatements n
st { subGraphs = sgs' }
sgRe :: DotSubGraph n -> m (DotSubGraph n)
sgRe DotSubGraph n
sg = do Maybe GraphID
sgid' <- case DotSubGraph n -> Maybe GraphID
forall n. DotSubGraph n -> Maybe GraphID
subGraphID DotSubGraph n
sg of
Maybe GraphID
Nothing -> do Int
n <- m Int
forall s (m :: * -> *). MonadState s m => m s
get
Int -> m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (Int -> m ()) -> Int -> m ()
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Enum a => a -> a
succ Int
n
Maybe GraphID -> m (Maybe GraphID)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe GraphID -> m (Maybe GraphID))
-> (Number -> Maybe GraphID) -> Number -> m (Maybe GraphID)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GraphID -> Maybe GraphID
forall a. a -> Maybe a
Just (GraphID -> Maybe GraphID)
-> (Number -> GraphID) -> Number -> Maybe GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Number -> GraphID
Num (Number -> m (Maybe GraphID)) -> Number -> m (Maybe GraphID)
forall a b. (a -> b) -> a -> b
$ Int -> Number
Int Int
n
Maybe GraphID
sgid -> Maybe GraphID -> m (Maybe GraphID)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GraphID
sgid
DotStatements n
stmts' <- DotStatements n -> m (DotStatements n)
stRe (DotStatements n -> m (DotStatements n))
-> DotStatements n -> m (DotStatements n)
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> DotStatements n
forall n. DotSubGraph n -> DotStatements n
subGraphStmts DotSubGraph n
sg
DotSubGraph n -> m (DotSubGraph n)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (DotSubGraph n -> m (DotSubGraph n))
-> DotSubGraph n -> m (DotSubGraph n)
forall a b. (a -> b) -> a -> b
$ DotSubGraph n
sg { subGraphID = sgid'
, subGraphStmts = stmts'
}
maxSGInt :: DotGraph n -> Int
maxSGInt :: forall n. DotGraph n -> Int
maxSGInt DotGraph n
dg = State Int () -> Int -> Int
forall s a. State s a -> s -> s
execState (DotStatements n -> State Int ()
forall {n}. DotStatements n -> State Int ()
stInt (DotStatements n -> State Int ())
-> DotStatements n -> State Int ()
forall a b. (a -> b) -> a -> b
$ DotGraph n -> DotStatements n
forall n. DotGraph n -> DotStatements n
graphStatements DotGraph n
dg)
(Int -> Int) -> (Maybe GraphID -> Int) -> Maybe GraphID -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe GraphID -> Int -> Int
`check` Int
0)
(Maybe GraphID -> Int) -> Maybe GraphID -> Int
forall a b. (a -> b) -> a -> b
$ DotGraph n -> Maybe GraphID
forall n. DotGraph n -> Maybe GraphID
graphID DotGraph n
dg
where
check :: Maybe GraphID -> Int -> Int
check = (Int -> Int) -> (Int -> Int -> Int) -> Maybe Int -> Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int -> Int
forall a. a -> a
id Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (Maybe Int -> Int -> Int)
-> (Maybe GraphID -> Maybe Int) -> Maybe GraphID -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GraphID -> Maybe Int
numericValue (GraphID -> Maybe Int) -> Maybe GraphID -> Maybe Int
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<)
stInt :: DotStatements n -> State Int ()
stInt = (DotSubGraph n -> State Int ()) -> [DotSubGraph n] -> State Int ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DotSubGraph n -> State Int ()
sgInt ([DotSubGraph n] -> State Int ())
-> (DotStatements n -> [DotSubGraph n])
-> DotStatements n
-> State Int ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotStatements n -> [DotSubGraph n]
forall n. DotStatements n -> [DotSubGraph n]
subGraphs
sgInt :: DotSubGraph n -> State Int ()
sgInt DotSubGraph n
sg = do (Int -> Int) -> State Int ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (Maybe GraphID -> Int -> Int
check (Maybe GraphID -> Int -> Int) -> Maybe GraphID -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> Maybe GraphID
forall n. DotSubGraph n -> Maybe GraphID
subGraphID DotSubGraph n
sg)
DotStatements n -> State Int ()
stInt (DotStatements n -> State Int ())
-> DotStatements n -> State Int ()
forall a b. (a -> b) -> a -> b
$ DotSubGraph n -> DotStatements n
forall n. DotSubGraph n -> DotStatements n
subGraphStmts DotSubGraph n
sg
class ToGraphID a where
toGraphID :: a -> GraphID
textGraphID :: Text -> GraphID
textGraphID :: Text -> GraphID
textGraphID = Text -> GraphID
forall a. ToGraphID a => a -> GraphID
toGraphID
instance ToGraphID Text where
toGraphID :: Text -> GraphID
toGraphID = Text -> GraphID
Str
instance ToGraphID String where
toGraphID :: String -> GraphID
toGraphID = Text -> GraphID
forall a. ToGraphID a => a -> GraphID
toGraphID (Text -> GraphID) -> (String -> Text) -> String -> GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance ToGraphID Char where
toGraphID :: Char -> GraphID
toGraphID = Text -> GraphID
forall a. ToGraphID a => a -> GraphID
toGraphID (Text -> GraphID) -> (Char -> Text) -> Char -> GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
instance ToGraphID Int where
toGraphID :: Int -> GraphID
toGraphID = Number -> GraphID
Num (Number -> GraphID) -> (Int -> Number) -> Int -> GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Number
Int
instance ToGraphID Integer where
toGraphID :: Integer -> GraphID
toGraphID = Number -> GraphID
Num (Number -> GraphID) -> (Integer -> Number) -> Integer -> GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Number
Int (Int -> Number) -> (Integer -> Int) -> Integer -> Number
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
instance ToGraphID Double where
toGraphID :: Double -> GraphID
toGraphID = Number -> GraphID
Num (Number -> GraphID) -> (Double -> Number) -> Double -> GraphID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Number
Dbl