Take a filename as a command-line arg, and use a marker process for main rather than SKIP

This commit is contained in:
Adam Sampson 2006-09-06 19:56:16 +00:00
parent 2e9d2123ad
commit 85eb9fe33d
3 changed files with 38 additions and 9 deletions

View File

@ -2,11 +2,17 @@
module Main where module Main where
import Text.ParserCombinators.Parsec import System
import Parse import Parse
main = do d <- getContents main :: IO ()
parseTest process (prepare d) main = do args <- getArgs
let fn = case args of
[fn] -> fn
_ -> error "Usage: fco [SOURCEFILE]"
putStr ("Compiling " ++ fn ++ "...\n")
tree <- parseSourceFile fn
putStr (show tree ++ "\n")

View File

@ -1,16 +1,19 @@
-- Parse occam code -- Parse occam code
module Parse where module Parse (parseSourceFile) where
import Data.List import Data.List
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import qualified Text.ParserCombinators.Parsec.Token as P import qualified Text.ParserCombinators.Parsec.Token as P
import Text.ParserCombinators.Parsec.Language (emptyDef) import Text.ParserCombinators.Parsec.Language (emptyDef)
import qualified IO
import Tree import Tree
-- ------------------------------------------------------------- -- -------------------------------------------------------------
mainMarker = "##MAGIC-FCO-MAIN-PROCESS##"
occamStyle occamStyle
= emptyDef = emptyDef
{ P.commentLine = "--" { P.commentLine = "--"
@ -98,7 +101,8 @@ occamStyle
"TYPE", "TYPE",
"VAL", "VAL",
"VALOF", "VALOF",
"WHILE" "WHILE",
mainMarker
] ]
, P.caseSensitive = True , P.caseSensitive = True
} }
@ -194,12 +198,17 @@ sTYPE = reserved "TYPE"
sVAL = reserved "VAL" sVAL = reserved "VAL"
sVALOF = reserved "VALOF" sVALOF = reserved "VALOF"
sWHILE = reserved "WHILE" sWHILE = reserved "WHILE"
sMainMarker = reserved mainMarker
-- XXX could handle VALOF by translating each step to one { and matching multiple ones? -- XXX could handle VALOF by translating each step to one { and matching multiple ones?
indent = symbol "{" indent = symbol "{"
outdent = symbol "}" outdent = symbol "}"
eol = symbol "@" eol = symbol "@"
-- -------------------------------------------------------------
-- These productions are based on the syntax in the occam2.1 manual.
abbreviation abbreviation
= try (do { n <- name ; sIS ; v <- variable ; sColon ; eol ; return $ OcIs n v }) = try (do { n <- name ; sIS ; v <- variable ; sColon ; eol ; return $ OcIs n v })
<|> try (do { s <- specifier ; n <- name ; sIS ; v <- variable ; sColon ; eol ; return $ OcIsType s n v }) <|> try (do { s <- specifier ; n <- name ; sIS ; v <- variable ; sColon ; eol ; return $ OcIsType s n v })
@ -591,6 +600,7 @@ process
<|> try alternation <|> try alternation
<|> try caseInput <|> try caseInput
<|> try procInstance <|> try procInstance
<|> try (do { sMainMarker ; eol ; return $ OcMainProcess })
<|> try (do { s <- specification ; p <- process ; return $ OcDecl s p }) <|> try (do { s <- specification ; p <- process ; return $ OcDecl s p })
<|> do { a <- allocation ; p <- process ; return $ OcDecl a p } <|> do { a <- allocation ; p <- process ; return $ OcDecl a p }
<?> "process" <?> "process"
@ -731,6 +741,14 @@ variant
-- ------------------------------------------------------------- -- -------------------------------------------------------------
-- This is only really true once we've tacked a process onto the bottom; a
-- source file is really a series of specifications, but the later ones need to
-- have the earlier ones in scope, so we can't parse them separately.
sourceFile = process
-- -------------------------------------------------------------
-- XXX this doesn't handle multi-line strings -- XXX this doesn't handle multi-line strings
-- XXX or VALOF processes -- XXX or VALOF processes
@ -770,11 +788,15 @@ flatten ls = concat $ intersperse "@" $ flatten' ls 0
-- ------------------------------------------------------------- -- -------------------------------------------------------------
-- XXX We have to tack SKIP on the end to make it a process.
-- XXX Doesn't handle preprocessor instructions. -- XXX Doesn't handle preprocessor instructions.
prepare d = flatten $ lines (d ++ "\nSKIP\n") prepare d = flatten $ lines (d ++ "\n" ++ mainMarker)
parseFile fn = do d <- readFile fn parseSourceFile :: String -> IO Node
parseTest process (prepare d) parseSourceFile fn
= do f <- IO.openFile fn IO.ReadMode
d <- IO.hGetContents f
return $ case (parse sourceFile "occam" $ prepare d) of
Left err -> error ("Parsing error: " ++ (show err))
Right defs -> defs

View File

@ -36,6 +36,7 @@ data Node =
| OcSeq [Node] | OcSeq [Node]
| OcSeqRep Node Node | OcSeqRep Node Node
| OcProcCall Node [Node] | OcProcCall Node [Node]
| OcMainProcess
| OcVars Node [Node] | OcVars Node [Node]
| OcIs Node Node | OcIs Node Node