module Data.GraphViz.Types.Canonical
       ( DotGraph(..)
         
       , DotStatements(..)
       , DotSubGraph(..)
         
       , GraphID(..)
       , GlobalAttributes(..)
       , DotNode(..)
       , DotEdge(..)
       ) where
import Data.GraphViz.Internal.State        (AttributeType (..))
import Data.GraphViz.Internal.Util         (bool)
import Data.GraphViz.Parsing
import Data.GraphViz.Printing
import Data.GraphViz.Types.Internal.Common
import Control.Arrow ((&&&))
data DotGraph n = DotGraph { strictGraph     :: Bool  
                           , directedGraph   :: Bool
                           , graphID         :: Maybe GraphID
                           , graphStatements :: DotStatements n
                           }
                deriving (Eq, Ord, Show, Read)
instance (PrintDot n) => PrintDot (DotGraph n) where
  unqtDot = printStmtBased printGraphID' (const GraphAttribute)
                           graphStatements toDot
    where
      printGraphID' = printGraphID strictGraph directedGraph graphID
instance (ParseDot n) => ParseDot (DotGraph n) where
  parseUnqt = parseGraphID DotGraph
              <*> parseBracesBased GraphAttribute parseUnqt
  parse = parseUnqt 
instance Functor DotGraph where
  fmap f g = g { graphStatements = fmap f $ graphStatements g }
data DotStatements n = DotStmts { attrStmts :: [GlobalAttributes]
                                , subGraphs :: [DotSubGraph n]
                                , nodeStmts :: [DotNode n]
                                , edgeStmts :: [DotEdge n]
                                }
                     deriving (Eq, Ord, Show, Read)
instance (PrintDot n) => PrintDot (DotStatements n) where
  unqtDot stmts = vcat $ sequence [ unqtDot $ attrStmts stmts
                                  , unqtDot $ subGraphs stmts
                                  , unqtDot $ nodeStmts stmts
                                  , unqtDot $ edgeStmts stmts
                                  ]
instance (ParseDot n) => ParseDot (DotStatements n) where
  parseUnqt = do atts <- tryParseList
                 newline'
                 sGraphs <- tryParseList
                 newline'
                 nodes <- tryParseList
                 newline'
                 edges <- tryParseList
                 return $ DotStmts atts sGraphs nodes edges
  parse = parseUnqt 
          `adjustErr`
          ("Not a valid set of statements\n\t"++)
instance Functor DotStatements where
  fmap f stmts = stmts { subGraphs = map (fmap f) $ subGraphs stmts
                       , nodeStmts = map (fmap f) $ nodeStmts stmts
                       , edgeStmts = map (fmap f) $ edgeStmts stmts
                       }
data DotSubGraph n = DotSG { isCluster     :: Bool
                           , subGraphID    :: Maybe GraphID
                           , subGraphStmts :: DotStatements n
                           }
                   deriving (Eq, Ord, Show, Read)
instance (PrintDot n) => PrintDot (DotSubGraph n) where
  unqtDot = printStmtBased printSubGraphID' subGraphAttrType
                           subGraphStmts toDot
  unqtListToDot = printStmtBasedList printSubGraphID' subGraphAttrType
                                     subGraphStmts toDot
  listToDot = unqtListToDot
subGraphAttrType :: DotSubGraph n -> AttributeType
subGraphAttrType = bool SubGraphAttribute ClusterAttribute . isCluster
printSubGraphID' :: DotSubGraph n -> DotCode
printSubGraphID' = printSubGraphID (isCluster &&& subGraphID)
instance (ParseDot n) => ParseDot (DotSubGraph n) where
  parseUnqt = parseSubGraph DotSG parseUnqt
              `onFail`
              
              fmap (DotSG False Nothing)
                   (parseBracesBased SubGraphAttribute parseUnqt)
  parse = parseUnqt 
          `adjustErr`
          ("Not a valid Sub Graph\n\t"++)
  parseUnqtList = sepBy (whitespace >> parseUnqt) newline'
  parseList = parseUnqtList
instance Functor DotSubGraph where
  fmap f sg = sg { subGraphStmts = fmap f $ subGraphStmts sg }