
This patch is a bit large, being as it encompasses two major changes: 1. The addition of the first version of a parallel usage checker. The usage checker uses the generics library (like the other passes) to work out if the parallel usage rules are broken. It mainly consists of: a) a function used to determine which variables are written to/read from in given bits of code, and b) a function that applies a) across the members of any par construct in the file, and checks that the expected usage rules hold The parallel usage checker is in an early stage, but I think the design is sensible - at least for doing the variable and array usage. The channel usage checker will require some slightly different functionality, and I am not considering the abbreviation checker yet. 2. As a consquence of adding a second test file (UsageCheckTest) alongside the first (RainParseTest), I have created a TestMain class that is intended to run all tests for all parts of Tock. I have also extracted some useful helper functions (for creating the expected results of tests) into a file named TestUtil. I've also modified the Makefil accordingly. There are a few other minor changes to RainParse/RainParseTest that are also included in the patch as separating them would have been tricky.
234 lines
6.7 KiB
Haskell
234 lines
6.7 KiB
Haskell
module RainParse where
|
|
|
|
import qualified Text.ParserCombinators.Parsec.Token as P
|
|
import Parse (tryXV)
|
|
|
|
|
|
|
|
|
|
|
|
--Chuck a whole load from Parse:
|
|
import Control.Monad (liftM, when)
|
|
import Control.Monad.Error (runErrorT)
|
|
import Control.Monad.State (MonadState, StateT, execStateT, liftIO, modify, get, put)
|
|
import Data.List
|
|
import qualified Data.Map as Map
|
|
import Data.Maybe
|
|
import Debug.Trace
|
|
import qualified IO
|
|
import Numeric (readHex)
|
|
import Text.ParserCombinators.Parsec
|
|
import Text.ParserCombinators.Parsec.Language (emptyDef)
|
|
import Text.Regex
|
|
|
|
import qualified AST as A
|
|
import CompState
|
|
import Errors
|
|
import EvalConstants
|
|
import EvalLiterals
|
|
import Indentation
|
|
import Intrinsics
|
|
import Metadata
|
|
import Pass
|
|
import Types
|
|
import Utils
|
|
|
|
|
|
|
|
--Dummy:
|
|
type RainState = Int
|
|
|
|
type RainParser = GenParser Char RainState
|
|
|
|
|
|
emptyState:: RainState
|
|
emptyState = 0
|
|
|
|
{-
|
|
instance MonadState st (GenParser tok st) where
|
|
get = getState
|
|
put = setState
|
|
|
|
instance Die (GenParser tok st) where
|
|
die = fail
|
|
-}
|
|
|
|
rainStyle
|
|
= emptyDef
|
|
{ P.commentLine = "#"
|
|
, P.nestedComments = False
|
|
, P.identStart = letter <|> char '_'
|
|
, P.identLetter = alphaNum <|> char '_'
|
|
, P.opStart = oneOf ":+-*/>=<!"
|
|
, P.opLetter = oneOf "+-="
|
|
, P.reservedOpNames= [
|
|
"+",
|
|
"-",
|
|
"*",
|
|
"/",
|
|
"==",
|
|
"<",
|
|
">",
|
|
">=",
|
|
"<=",
|
|
"!=",
|
|
"-",
|
|
":"
|
|
]
|
|
, P.reservedNames = [
|
|
"par",
|
|
"seq",
|
|
"alt",
|
|
"seqeach",
|
|
"pareach",
|
|
"channel",
|
|
"one2one",
|
|
"int",
|
|
"if",
|
|
"while",
|
|
"process",
|
|
"bool"
|
|
{-
|
|
"tuple",
|
|
"sleep",
|
|
"for",
|
|
"until",
|
|
"poison",
|
|
"return",
|
|
"function",
|
|
"typedef",
|
|
"sint8","sint16","sint32","sint64"
|
|
"uint8","uint16","uint32","uint64"
|
|
"shared",
|
|
"template",
|
|
"constant",
|
|
"namespace"
|
|
-}
|
|
]
|
|
, P.caseSensitive = True
|
|
}
|
|
|
|
lexer :: P.TokenParser RainState
|
|
lexer = P.makeTokenParser rainStyle
|
|
|
|
whiteSpace = P.whiteSpace lexer
|
|
lexeme = P.lexeme lexer
|
|
symbol = P.symbol lexer
|
|
natural = P.natural lexer
|
|
parens = P.parens lexer
|
|
semi = P.semi lexer
|
|
identifier = P.identifier lexer
|
|
reserved = P.reserved lexer
|
|
reservedOp = P.reservedOp lexer
|
|
|
|
--{{{ Symbols
|
|
sLeftQ = try $ symbol "["
|
|
sRightQ = try $ symbol "]"
|
|
sLeftR = try $ symbol "("
|
|
sRightR = try $ symbol ")"
|
|
sLeftC = try $ symbol "{"
|
|
sRightC = try $ symbol "}"
|
|
sEquality = try $ symbol "=="
|
|
sSemiColon = try $ symbol ";"
|
|
--}}}
|
|
|
|
--{{{ Keywords
|
|
|
|
sPar = reserved "par"
|
|
sSeq = reserved "seq"
|
|
sAlt = reserved "alt"
|
|
sSeqeach = reserved "seqeach"
|
|
sPareach = reserved "pareach"
|
|
sChannel = reserved "channel"
|
|
sOne2One = reserved "one2one"
|
|
sBool = reserved "bool"
|
|
sInt = reserved "int"
|
|
sIf = reserved "if"
|
|
sElse = reserved "else"
|
|
sWhile = reserved "while"
|
|
sProcess = reserved "process"
|
|
--}}}
|
|
|
|
--{{{Ideas nicked from GenerateC:
|
|
md :: RainParser Meta
|
|
md
|
|
= do pos <- getPosition
|
|
return Meta {
|
|
metaFile = Just $ sourceName pos,
|
|
metaLine = sourceLine pos,
|
|
metaColumn = sourceColumn pos
|
|
}
|
|
|
|
name :: A.NameType -> RainParser A.Name
|
|
name nt
|
|
= do m <- md
|
|
s <- identifier
|
|
return $ A.Name m nt s
|
|
<?> show nt
|
|
|
|
--}}}
|
|
|
|
dataType :: RainParser A.Type
|
|
dataType
|
|
= do {sBool ; return A.Bool}
|
|
<|> do {sInt ; return A.Int64}
|
|
<|> do {sChannel ; inner <- dataType ; return $ A.Chan inner}
|
|
<?> "data type"
|
|
|
|
variableId :: RainParser A.Variable
|
|
variableId = do {m <- md ; v <- (name A.VariableName) ; return $ A.Variable m v}
|
|
<?> "variable name"
|
|
|
|
|
|
expression :: RainParser A.Expression
|
|
expression
|
|
= do {m <- md ; lhs <- subExpression ;
|
|
do {sEquality ; rhs <- expression ; return $ A.Dyadic m A.Eq lhs rhs}
|
|
<|> do {return lhs}
|
|
}
|
|
<?> "expression"
|
|
|
|
subExpression :: RainParser A.Expression
|
|
subExpression
|
|
= do {m <- md ; id <- variableId ; return $ A.ExprVariable m id}
|
|
<?> "[sub-]expression"
|
|
|
|
block :: RainParser A.Structured
|
|
block = do {m <- md ; sLeftC ; procs <- (many statement) ; sts <- sequence (map wrapProc procs) ; sRightC ; return $ A.Several m sts}
|
|
where
|
|
wrapProc :: A.Process -> RainParser A.Structured
|
|
wrapProc x = return (A.OnlyP emptyMeta x)
|
|
|
|
optionalSeq :: RainParser ()
|
|
optionalSeq = option () sSeq
|
|
|
|
assignOp :: RainParser (Meta, Maybe A.DyadicOp)
|
|
--consume an optional operator, then an equals sign (so we can handle = += /= etc) This should not handle !=, nor crazy things like ===, <== (nor <=)
|
|
assignOp
|
|
= do {m <- md; reservedOp "+=" ; return (m,Just A.Plus)}
|
|
<|> do {m <- md; reservedOp "-=" ; return (m,Just A.Minus)}
|
|
<|> do {m <- md; reservedOp "=" ; return (m,Nothing)}
|
|
--TODO the rest
|
|
|
|
lvalue :: RainParser A.Variable
|
|
--For now, only handle plain variables:
|
|
lvalue = variableId
|
|
|
|
statement :: RainParser A.Process
|
|
statement
|
|
= do { m <- md ; sWhile ; sLeftR ; exp <- expression ; sRightR ; st <- statement ; return $ A.While m exp st}
|
|
<|> do { m <- md ; sIf ; sLeftR ; exp <- expression ; sRightR ; st <- statement ;
|
|
option (A.If m $ A.Several m [A.OnlyC m (A.Choice m exp st), A.OnlyC m (A.Choice m (A.True m) (A.Skip m))])
|
|
(do {sElse ; elSt <- statement ; return (A.If m $ A.Several m [A.OnlyC m (A.Choice m exp st), A.OnlyC m (A.Choice m (A.True m) elSt)])})
|
|
}
|
|
<|> do { m <- md ; optionalSeq ; b <- block ; return $ A.Seq m b}
|
|
<|> do { m <- md ; sPar ; b <- block ; return $ A.Par m A.PlainPar b}
|
|
<|> do { m <- md ; lv <- lvalue ; op <- assignOp ; exp <- expression ; sSemiColon ;
|
|
case op of
|
|
(m', Just dyOp) -> return (A.Assign m' [lv] (A.ExpressionList m' [(A.Dyadic m' dyOp (A.ExprVariable m lv) exp)]))
|
|
(m', Nothing) -> return (A.Assign m' [lv] (A.ExpressionList m [exp]))
|
|
}
|
|
<|> do { m <- md ; sSemiColon ; return $ A.Skip m}
|
|
<?> "statement"
|
|
--TODO the "each" statements
|