module PP.Templates.Dfa
( DfaContext
, context
) where
import Data.Data
import qualified Data.Graph.Inductive.Graph as Gr
import Data.Typeable
import PP.Builder
import PP.Template
import Text.StringTemplate
import Text.StringTemplate.GenericStandard
data DfaContext = DfaContext
{ states :: [DfaContextState]
, transitions :: [DfaContextTransition]
} deriving (Data, Typeable, Eq)
data DfaContextState = DfaContextState
{ id :: Int
, isInitial :: Bool
, isNode :: Bool
, isFinal :: Bool
, final :: String
} deriving (Data, Typeable, Eq)
data DfaContextTransition = DfaContextTransition
{ from :: Int
, to :: Int
, symbol :: Char
} deriving (Data, Typeable, Eq)
context :: DfaGraph -> DfaContext
context dfa = DfaContext states' transitions'
where
states' = map fromNode $ Gr.labNodes dfa
transitions' = map fromEdge $ Gr.labEdges dfa
fromNode (i, DfaInitial) = DfaContextState i True False False ""
fromNode (i, DfaNode) = DfaContextState i False True False ""
fromNode (i, DfaFinal f) = DfaContextState i False False True f
fromEdge (i, j, DfaValue s) = DfaContextTransition i j s
instance Template DfaContext where
attributes = setAttribute "dfa"