{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses #-}
module Data.GraphViz.Types.Monadic
( Dot
, DotM
, GraphID(..)
, digraph
, digraph'
, graph
, graph'
, graphAttrs
, nodeAttrs
, edgeAttrs
, subgraph
, anonSubgraph
, cluster
, node
, node'
, edge
, (-->)
, (<->)
) where
import Data.GraphViz.Attributes (Attributes)
import Data.GraphViz.Types.Generalised
import Data.DList (DList)
import qualified Data.DList as DL
import qualified Data.Sequence as Seq
#if !(MIN_VERSION_base (4,8,0))
import Control.Applicative (Applicative(..))
import Data.Monoid (Monoid(..))
#endif
#if MIN_VERSION_base (4,9,0) && !MIN_VERSION_base (4,13,0)
import Data.Semigroup (Semigroup(..))
#endif
import Control.Monad.Fix (MonadFix (mfix))
type Dot n = DotM n ()
newtype DotM n a = DotM { runDot :: (a, DotStmts n) }
execDot :: DotM n a -> DotStmts n
execDot = snd . runDot
instance Functor (DotM n) where
fmap f (DotM (a,stmts)) = DotM (f a, stmts)
instance Applicative (DotM n) where
pure = DotM . flip (,) DL.empty
(DotM (f,stmts1)) <*> (DotM (a,stmts2)) = DotM (f a, stmts1 `DL.append` stmts2)
instance Monad (DotM n) where
return = pure
dt >>= f = DotM
$ let ~(a,stmts) = runDot dt
~(b,stmts') = runDot $ f a
in (b, stmts `DL.append` stmts')
instance MonadFix (DotM n) where
mfix m = let (a,n) = runDot $ m a
in DotM (a,n)
#if MIN_VERSION_base (4,9,0)
instance Semigroup a => Semigroup (DotM n a) where
DotM x1 <> DotM x2 = DotM (x1 <> x2)
#endif
instance Monoid a => Monoid (DotM n a) where
mappend (DotM x1) (DotM x2) = DotM (mappend x1 x2)
mempty = DotM mempty
tell :: DotStmts n -> Dot n
tell = DotM . (,) ()
tellStmt :: DotStmt n -> Dot n
tellStmt = tell . DL.singleton
digraph :: GraphID -> DotM n a -> DotGraph n
digraph = mkGraph True . Just
digraph' :: DotM n a -> DotGraph n
digraph' = mkGraph True Nothing
graph :: GraphID -> DotM n a -> DotGraph n
graph = mkGraph False . Just
graph' :: DotM n a -> DotGraph n
graph' = mkGraph False Nothing
mkGraph :: Bool -> Maybe GraphID -> DotM n a -> DotGraph n
mkGraph isDir mid dot = DotGraph { strictGraph = False
, directedGraph = isDir
, graphID = mid
, graphStatements = execStmts dot
}
type DotStmts n = DList (DotStmt n)
execStmts :: DotM n a -> DotStatements n
execStmts = convertStatements . execDot
convertStatements :: DotStmts n -> DotStatements n
convertStatements = Seq.fromList . map convertStatement . DL.toList
data DotStmt n = MA GlobalAttributes
| MS (Subgraph n)
| MN (DotNode n)
| ME (DotEdge n)
convertStatement :: DotStmt n -> DotStatement n
convertStatement (MA gas) = GA gas
convertStatement (MS sg) = SG . DotSG (sgIsClust sg) (sgID sg)
. execStmts $ sgStmts sg
convertStatement (MN dn) = DN dn
convertStatement (ME de) = DE de
graphAttrs :: Attributes -> Dot n
graphAttrs = tellStmt . MA . GraphAttrs
nodeAttrs :: Attributes -> Dot n
nodeAttrs = tellStmt . MA . NodeAttrs
edgeAttrs :: Attributes -> Dot n
edgeAttrs = tellStmt . MA . EdgeAttrs
data Subgraph n = Sg { sgIsClust :: Bool
, sgID :: Maybe GraphID
, sgStmts :: Dot n
}
subgraph :: GraphID -> DotM n a -> Dot n
subgraph = nonClust . Just
anonSubgraph :: DotM n a -> Dot n
anonSubgraph = nonClust Nothing
nonClust :: Maybe GraphID -> DotM n a -> Dot n
nonClust = createSubGraph False
createSubGraph :: Bool -> Maybe GraphID -> DotM n a -> Dot n
createSubGraph isCl mid = tellStmt . MS . Sg isCl mid . (>> return ())
cluster :: GraphID -> DotM n a -> Dot n
cluster = createSubGraph True . Just
node :: n -> Attributes -> Dot n
node n = tellStmt . MN . DotNode n
node' :: n -> Dot n
node' = (`node` [])
edge :: n -> n -> Attributes -> Dot n
edge f t = tellStmt . ME . DotEdge f t
(-->) :: n -> n -> Dot n
f --> t = edge f t []
infixr 9 -->
(<->) :: n -> n -> Dot n
(<->) = (-->)
infixr 9 <->