Skip to content
Snippets Groups Projects
Commit 46937cf8 authored by Hans-Peter Deifel's avatar Hans-Peter Deifel
Browse files

Add separate CFG.Types module

parent 24be4ed6
Branches
Tags
No related merge requests found
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
module CFG.Graph module CFG.Graph
( CFG(..) ( graphify
, P.Block(..)
, graphify
) where ) where
import Data.Graph import Data.Graph
import qualified CFG.Parser as P
import Data.Text (Text) import Data.Text (Text)
data CFG = CFG import CFG.Types
{ graph :: Graph
, getBlock :: Vertex -> (P.Block, Text, [Text])
, getVertex :: Text -> Maybe Vertex
}
instance Show CFG where graphify :: Function -> CFG
show = show . graph
graphify :: P.Function -> CFG
graphify function = CFG g ver2node key2vert graphify function = CFG g ver2node key2vert
where (g, ver2node, key2vert) = graphFromEdges $ graphList function where (g, ver2node, key2vert) = graphFromEdges $ graphList function
graphList :: P.Function -> [(P.Block, Text, [Text])] graphList :: Function -> [(Block, Text, [Text])]
graphList = map iter . P.blocks graphList = map iter . funBlocks
where iter b = (b, P.name (b :: P.Block), P.successors b) where iter b = (b, blkName (b :: Block), blkSuccessors b)
...@@ -13,7 +13,7 @@ import Data.Text (Text) ...@@ -13,7 +13,7 @@ import Data.Text (Text)
import Data.Graph import Data.Graph
import Data.Array import Data.Array
import CFG.Graph import CFG.Types
-- | Identifier, used for labels and function names -- | Identifier, used for labels and function names
type Ident = Text type Ident = Text
...@@ -35,7 +35,7 @@ flattenCFG :: Vertex -- ^ Start node ...@@ -35,7 +35,7 @@ flattenCFG :: Vertex -- ^ Start node
-> [Instr] -> [Instr]
flattenCFG startNode cfg = flattenCFG startNode cfg =
Goto (vertexToIdent cfg startNode) Goto (vertexToIdent cfg startNode)
: concatMap (compileBlock cfg) (vertices $ graph cfg) : concatMap (compileBlock cfg) (vertices $ cfgGraph cfg)
-- TODO Better (unambiguous) name for the out label -- TODO Better (unambiguous) name for the out label
++ [Label "out"] ++ [Label "out"]
...@@ -48,7 +48,7 @@ compileBlock cfg vertex = ...@@ -48,7 +48,7 @@ compileBlock cfg vertex =
where ident = vertexToIdent cfg vertex where ident = vertexToIdent cfg vertex
call = [] -- TODO call = [] -- TODO
gotoSuccs = case graph cfg ! vertex of gotoSuccs = case cfgGraph cfg ! vertex of
[] -> Goto "out" -- no successors [] -> Goto "out" -- no successors
[successor] -> Goto (vertexToIdent cfg successor) [successor] -> Goto (vertexToIdent cfg successor)
[left, right] -> IfThanElse vertex [left, right] -> IfThanElse vertex
...@@ -59,4 +59,4 @@ compileBlock cfg vertex = ...@@ -59,4 +59,4 @@ compileBlock cfg vertex =
vertexToIdent :: CFG -> Vertex -> Ident vertexToIdent :: CFG -> Vertex -> Ident
vertexToIdent cfg vertex = key vertexToIdent cfg vertex = key
where (_, key, _) = getBlock cfg vertex where (_, key, _) = cfgGetBlock cfg vertex
...@@ -2,10 +2,6 @@ ...@@ -2,10 +2,6 @@
module CFG.Parser module CFG.Parser
( parseFile ( parseFile
, file , file
, Function(..)
, FunctionKind(..)
, Block(..)
, CallInfo(..)
) where ) where
import Text.Megaparsec import Text.Megaparsec
...@@ -13,31 +9,11 @@ import Text.Megaparsec.Text ...@@ -13,31 +9,11 @@ import Text.Megaparsec.Text
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import CFG.Types
parseFile :: FilePath -> Text -> Either (ParseError Char Dec) [Function] parseFile :: FilePath -> Text -> Either (ParseError Char Dec) [Function]
parseFile = parse file parseFile = parse file
data Function = Function
{ kind :: FunctionKind
, name :: Text
, subtask :: Text
, entryNode :: Text
, blocks :: [Block]
}
deriving (Show, Eq)
data FunctionKind = KindFunction | KindSubtask
deriving (Show, Eq)
data Block = Block
{ name :: Text
, successors :: [Text]
, callInfo :: Maybe CallInfo
}
deriving (Show, Eq)
data CallInfo = FunctionCall Text | SystemCall Text
deriving (Show, Eq)
file :: Parser [Function] file :: Parser [Function]
file = many function file = many function
......
module CFG.Types where
import Data.Text (Text)
import Data.Graph
data Function = Function
{ funKind :: FunctionKind
, funName :: Text
, funSubtask :: Text
, funEntryNode :: Text
, funBlocks :: [Block]
}
deriving (Show, Eq)
data FunctionKind = KindFunction | KindSubtask
deriving (Show, Eq)
data Block = Block
{ blkName :: Text
, blkSuccessors :: [Text]
, blkCallInfo :: Maybe CallInfo
}
deriving (Show, Eq)
data CallInfo = FunctionCall Text | SystemCall Text
deriving (Show, Eq)
data CFG = CFG
{ cfgGraph :: Graph
, cfgGetBlock :: Vertex -> (Block, Text, [Text])
, cfgGetVertex :: Text -> Maybe Vertex
}
instance Show CFG where
show = show . cfgGraph
...@@ -17,6 +17,7 @@ library ...@@ -17,6 +17,7 @@ library
, CFG.Graph , CFG.Graph
, CFG.IR , CFG.IR
, CFG.C , CFG.C
, CFG.Types
hs-source-dirs: src hs-source-dirs: src
build-depends: base >=4.8 && <4.10 build-depends: base >=4.8 && <4.10
, megaparsec >= 5 && <5.1 , megaparsec >= 5 && <5.1
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment