{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module Data.GraphViz.Types.Internal.Common
( GraphID (..)
, Number (..)
, numericValue
, GlobalAttributes (..)
, partitionGlobal
, unPartitionGlobal
, withGlob
, DotNode (..)
, DotEdge (..)
, parseEdgeLine
, printGraphID
, parseGraphID
, printStmtBased
, printStmtBasedList
, printSubGraphID
, parseSubGraph
, parseBracesBased
, parseStatements
) where
import Data.GraphViz.Attributes.Complete (Attribute(HeadPort, TailPort),
Attributes, Number(..),
usedByClusters, usedByGraphs,
usedByNodes)
import Data.GraphViz.Attributes.Internal (PortPos, parseEdgeBasedPP)
import Data.GraphViz.Internal.State
import Data.GraphViz.Internal.Util
import Data.GraphViz.Parsing
import Data.GraphViz.Printing
import Control.Monad (unless, when)
import Data.Maybe (isJust)
import Data.Monoid ((<>))
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.Read as T
data GraphID = Str Text
| Num Number
deriving (Eq, Ord, Show, Read)
instance PrintDot GraphID where
unqtDot (Str str) = unqtDot str
unqtDot (Num n) = unqtDot n
toDot (Str str) = toDot str
toDot (Num n) = toDot n
instance ParseDot GraphID where
parseUnqt = stringNum <$> parseUnqt
parse = stringNum <$> parse
`adjustErr`
("Not a valid GraphID\n\t"++)
stringNum :: Text -> GraphID
stringNum str = maybe checkDbl (Num . Int) $ stringToInt str
where
checkDbl = if isNumString True str
then Num . Dbl $ toDouble str
else Str str
numericValue :: GraphID -> Maybe Int
numericValue (Str str) = either (const Nothing) (Just . round . fst)
$ T.signed T.double str
numericValue (Num n) = case n of
Int i -> Just i
Dbl d -> Just $ round d
data GlobalAttributes = GraphAttrs { attrs :: Attributes }
| NodeAttrs { attrs :: Attributes }
| EdgeAttrs { attrs :: Attributes }
deriving (Eq, Ord, Show, Read)
instance PrintDot GlobalAttributes where
unqtDot = printAttrBased True printGlobAttrType globAttrType attrs
unqtListToDot = printAttrBasedList True printGlobAttrType globAttrType attrs
listToDot = unqtListToDot
partitionGlobal :: [GlobalAttributes] -> (Attributes, Attributes, Attributes)
partitionGlobal = foldr select ([], [], [])
where
select globA ~(gs,ns,es) = case globA of
GraphAttrs as -> (as ++ gs, ns, es)
NodeAttrs as -> (gs, as ++ ns, es)
EdgeAttrs as -> (gs, ns, as ++ es)
unPartitionGlobal :: (Attributes, Attributes, Attributes) -> [GlobalAttributes]
unPartitionGlobal (gas,nas,eas) = [ GraphAttrs gas
, NodeAttrs nas
, EdgeAttrs eas
]
printGlobAttrType :: GlobalAttributes -> DotCode
printGlobAttrType GraphAttrs{} = text "graph"
printGlobAttrType NodeAttrs{} = text "node"
printGlobAttrType EdgeAttrs{} = text "edge"
instance ParseDot GlobalAttributes where
parseUnqt = do gat <- parseGlobAttrType
let mtp = globAttrType $ gat []
oldTp <- getAttributeType
maybe (return ()) setAttributeType mtp
as <- whitespace *> parse
setAttributeType oldTp
return $ gat as
`onFail`
fmap determineType parse
parse = parseUnqt
`adjustErr`
("Not a valid listing of global attributes\n\t"++)
parseUnqtList = parseStatements parseUnqt
parseList = parseUnqtList
globAttrType :: GlobalAttributes -> Maybe AttributeType
globAttrType NodeAttrs{} = Just NodeAttribute
globAttrType EdgeAttrs{} = Just EdgeAttribute
globAttrType _ = Nothing
parseGlobAttrType :: Parse (Attributes -> GlobalAttributes)
parseGlobAttrType = oneOf [ stringRep GraphAttrs "graph"
, stringRep NodeAttrs "node"
, stringRep EdgeAttrs "edge"
]
determineType :: Attribute -> GlobalAttributes
determineType attr
| usedByGraphs attr = GraphAttrs attr'
| usedByClusters attr = GraphAttrs attr'
| usedByNodes attr = NodeAttrs attr'
| otherwise = EdgeAttrs attr'
where
attr' = [attr]
withGlob :: (Attributes -> Attributes) -> GlobalAttributes -> GlobalAttributes
withGlob f (GraphAttrs as) = GraphAttrs $ f as
withGlob f (NodeAttrs as) = NodeAttrs $ f as
withGlob f (EdgeAttrs as) = EdgeAttrs $ f as
data DotNode n = DotNode { nodeID :: n
, nodeAttributes :: Attributes
}
deriving (Eq, Ord, Show, Read)
instance (PrintDot n) => PrintDot (DotNode n) where
unqtDot = printAttrBased False printNodeID
(const $ Just NodeAttribute) nodeAttributes
unqtListToDot = printAttrBasedList False printNodeID
(const $ Just NodeAttribute) nodeAttributes
listToDot = unqtListToDot
printNodeID :: (PrintDot n) => DotNode n -> DotCode
printNodeID = toDot . nodeID
instance (ParseDot n) => ParseDot (DotNode n) where
parseUnqt = parseAttrBased NodeAttribute False parseNodeID
parse = parseUnqt
parseUnqtList = parseAttrBasedList NodeAttribute False parseNodeID
parseList = parseUnqtList
parseNodeID :: (ParseDot n) => Parse (Attributes -> DotNode n)
parseNodeID = DotNode <$> parseAndCheck
where
parseAndCheck = do n <- parse
me <- optional parseUnwanted
maybe (return n) (const notANode) me
notANode = fail "This appears to be an edge, not a node"
parseUnwanted = oneOf [ parseEdgeType *> return ()
, character ':' *> return ()
]
instance Functor DotNode where
fmap f n = n { nodeID = f $ nodeID n }
data DotEdge n = DotEdge { fromNode :: n
, toNode :: n
, edgeAttributes :: Attributes
}
deriving (Eq, Ord, Show, Read)
instance (PrintDot n) => PrintDot (DotEdge n) where
unqtDot = printAttrBased False printEdgeID
(const $ Just EdgeAttribute) edgeAttributes
unqtListToDot = printAttrBasedList False printEdgeID
(const $ Just EdgeAttribute) edgeAttributes
listToDot = unqtListToDot
printEdgeID :: (PrintDot n) => DotEdge n -> DotCode
printEdgeID e = do isDir <- getDirectedness
toDot (fromNode e)
<+> bool undirEdge' dirEdge' isDir
<+> toDot (toNode e)
instance (ParseDot n) => ParseDot (DotEdge n) where
parseUnqt = parseAttrBased EdgeAttribute False parseEdgeID
parse = parseUnqt
parseUnqtList = concat <$> parseStatements parseEdgeLine
parseList = parseUnqtList
parseEdgeID :: (ParseDot n) => Parse (Attributes -> DotEdge n)
parseEdgeID = ignoreSep mkEdge parseEdgeNode parseEdgeType parseEdgeNode
`adjustErr`
("Parsed beginning of DotEdge but could not parse Attributes:\n\t"++)
type EdgeNode n = (n, Maybe PortPos)
parseEdgeNodes :: (ParseDot n) => Parse [EdgeNode n]
parseEdgeNodes = oneOf [ parseBraced (wrapWhitespace
$ parseStatements parseEdgeNode)
, sepBy1 parseEdgeNode (wrapWhitespace parseComma)
, (: []) <$> parseEdgeNode
]
parseEdgeNode :: (ParseDot n) => Parse (EdgeNode n)
parseEdgeNode = liftA2 (,) parse
(optional $ character ':' *> parseEdgeBasedPP)
mkEdge :: EdgeNode n -> EdgeNode n -> Attributes -> DotEdge n
mkEdge (eFrom, mFP) (eTo, mTP) = DotEdge eFrom eTo
. addPortPos TailPort mFP
. addPortPos HeadPort mTP
mkEdges :: [EdgeNode n] -> [EdgeNode n]
-> Attributes -> [DotEdge n]
mkEdges fs ts as = liftA2 (\f t -> mkEdge f t as) fs ts
addPortPos :: (PortPos -> Attribute) -> Maybe PortPos
-> Attributes -> Attributes
addPortPos c = maybe id ((:) . c)
parseEdgeType :: Parse Bool
parseEdgeType = wrapWhitespace $ stringRep True dirEdge
`onFail`
stringRep False undirEdge
parseEdgeLine :: (ParseDot n) => Parse [DotEdge n]
parseEdgeLine = do n1 <- parseEdgeNodes
ens <- many1 $ parseEdgeType *> parseEdgeNodes
let ens' = n1 : ens
efs = zipWith mkEdges ens' (tail ens')
ef = return $ \ as -> concatMap ($as) efs
parseAttrBased EdgeAttribute False ef
instance Functor DotEdge where
fmap f e = e { fromNode = f $ fromNode e
, toNode = f $ toNode e
}
dirEdge :: String
dirEdge = "->"
dirEdge' :: DotCode
dirEdge' = text $ T.pack dirEdge
undirEdge :: String
undirEdge = "--"
undirEdge' :: DotCode
undirEdge' = text $ T.pack undirEdge
dirGraph :: String
dirGraph = "digraph"
dirGraph' :: DotCode
dirGraph' = text $ T.pack dirGraph
undirGraph :: String
undirGraph = "graph"
undirGraph' :: DotCode
undirGraph' = text $ T.pack undirGraph
strGraph :: String
strGraph = "strict"
strGraph' :: DotCode
strGraph' = text $ T.pack strGraph
sGraph :: String
sGraph = "subgraph"
sGraph' :: DotCode
sGraph' = text $ T.pack sGraph
clust :: String
clust = "cluster"
clust' :: DotCode
clust' = text $ T.pack clust
printGraphID :: (a -> Bool) -> (a -> Bool)
-> (a -> Maybe GraphID)
-> a -> DotCode
printGraphID str isDir mID g = do setDirectedness isDir'
bool empty strGraph' (str g)
<+> bool undirGraph' dirGraph' isDir'
<+> maybe empty toDot (mID g)
where
isDir' = isDir g
parseGraphID :: (Bool -> Bool -> Maybe GraphID -> a) -> Parse a
parseGraphID f = do whitespace
str <- isJust <$> optional (parseAndSpace $ string strGraph)
dir <- parseAndSpace ( stringRep True dirGraph
`onFail`
stringRep False undirGraph
)
setDirectedness dir
gID <- optional $ parseAndSpace parse
return $ f str dir gID
printStmtBased :: (a -> DotCode) -> (a -> AttributeType)
-> (a -> stmts) -> (stmts -> DotCode)
-> a -> DotCode
printStmtBased f ftp r dr a = do gs <- getsGS id
setAttributeType $ ftp a
dc <- printBracesBased (f a) (dr $ r a)
modifyGS (const gs)
return dc
printStmtBasedList :: (a -> DotCode) -> (a -> AttributeType)
-> (a -> stmts) -> (stmts -> DotCode)
-> [a] -> DotCode
printStmtBasedList f ftp r dr = vcat . mapM (printStmtBased f ftp r dr)
printBracesBased :: DotCode -> DotCode -> DotCode
printBracesBased h i = vcat $ sequence [ h <+> lbrace
, ind i
, rbrace
]
where
ind = indent 4
parseBracesBased :: AttributeType -> Parse a -> Parse a
parseBracesBased tp p = do gs <- getsGS id
setAttributeType tp
a <- whitespace *> parseBraced (wrapWhitespace p)
modifyGS (const gs)
return a
`adjustErr`
("Not a valid value wrapped in braces.\n\t"++)
printSubGraphID :: (a -> (Bool, Maybe GraphID)) -> a -> DotCode
printSubGraphID f a = sGraph'
<+> maybe cl dtID mID
where
(isCl, mID) = f a
cl = bool empty clust' isCl
dtID = printSGID isCl
printSGID :: Bool -> GraphID -> DotCode
printSGID isCl sID = bool noClust addClust isCl
where
noClust = toDot sID
addClust = toDot . T.append (T.pack clust) . T.cons '_'
. renderDot $ mkDot sID
mkDot (Str str) = text str
mkDot gid = unqtDot gid
parseSubGraph :: (Bool -> Maybe GraphID -> stmt -> c) -> Parse stmt -> Parse c
parseSubGraph pid pst = do (isC, fID) <- parseSubGraphID pid
let tp = bool SubGraphAttribute ClusterAttribute isC
fID <$> parseBracesBased tp pst
parseSubGraphID :: (Bool -> Maybe GraphID -> c) -> Parse (Bool,c)
parseSubGraphID f = appl <$> (string sGraph *> whitespace1 *> parseSGID)
where
appl (isC, mid) = (isC, f isC mid)
parseSGID :: Parse (Bool, Maybe GraphID)
parseSGID = oneOf [ getClustFrom <$> parseAndSpace parse
, return (False, Nothing)
]
where
getClustFrom (Str str) = runParser' pStr str
getClustFrom gid = (False, Just gid)
checkCl = stringRep True clust
pStr = do isCl <- checkCl
`onFail`
return False
when isCl $ optional (character '_') *> return ()
sID <- optional pID
let sID' = if sID == emptyID
then Nothing
else sID
return (isCl, sID')
emptyID = Just $ Str ""
pID = stringNum <$> manySatisfy (const True)
printAttrBased :: Bool -> (a -> DotCode) -> (a -> Maybe AttributeType)
-> (a -> Attributes) -> a -> DotCode
printAttrBased prEmp ff ftp fas a = do oldType <- getAttributeType
maybe (return ()) setAttributeType mtp
oldCS <- getColorScheme
(dc <> semi) <* unless prEmp (setColorScheme oldCS)
<* setAttributeType oldType
where
mtp = ftp a
f = ff a
dc = case fas a of
[] | not prEmp -> f
as -> f <+> toDot as
printAttrBasedList :: Bool -> (a -> DotCode) -> (a -> Maybe AttributeType)
-> (a -> Attributes) -> [a] -> DotCode
printAttrBasedList prEmp ff ftp fas = vcat . mapM (printAttrBased prEmp ff ftp fas)
parseAttrBased :: AttributeType -> Bool -> Parse (Attributes -> a) -> Parse a
parseAttrBased tp lc p = do oldType <- getAttributeType
setAttributeType tp
oldCS <- getColorScheme
f <- p
atts <- tryParseList' (whitespace *> parse)
unless lc $ setColorScheme oldCS
when (tp /= oldType) $ setAttributeType oldType
return $ f atts
`adjustErr`
("Not a valid attribute-based structure\n\t"++)
parseAttrBasedList :: AttributeType -> Bool -> Parse (Attributes -> a) -> Parse [a]
parseAttrBasedList tp lc = parseStatements . parseAttrBased tp lc
statementEnd :: Parse ()
statementEnd = parseSplit *> newline'
where
parseSplit = (whitespace *> oneOf [ character ';' *> return ()
, newline
]
)
`onFail`
whitespace1
parseStatements :: Parse a -> Parse [a]
parseStatements p = sepBy (whitespace *> p) statementEnd
`discard`
optional statementEnd