Fixed the backends to work with the new system (mainly removing unnecessary code)
This commit is contained in:
parent
e1c18cc082
commit
6d6d26d5d6
|
@ -146,7 +146,8 @@ transformWaitFor = cOnlyPass "Transform wait for guards into wait until guards"
|
|||
put (specs ++ [A.Spec m (A.Specification m n (A.Declaration m A.Time))],
|
||||
init ++ [A.Only m $ A.Input m tim
|
||||
(A.InputTimerRead m (A.InVariable m var)),
|
||||
A.Only m $ A.Assign m [var] $ A.ExpressionList m [A.Dyadic m A.Plus (A.ExprVariable m var) e]])
|
||||
A.Only m $ A.Assign m [var] $ A.ExpressionList m
|
||||
[addExprsInt (A.ExprVariable m var) e]])
|
||||
return $ A.Only m'' $ A.Alternative m cond tim (A.InputTimerAfter m' (A.ExprVariable m' var)) p
|
||||
|
||||
doWaitFor m a = return $ A.Only m a
|
||||
|
@ -274,7 +275,7 @@ declareSizesArray = occamOnlyPass "Declare array-size arrays"
|
|||
-- together the dimensions.
|
||||
(_, A.Array ds t) ->
|
||||
do BIJust elementSize <- bytesInType t
|
||||
return $ foldl mulExprs elementSize dSizes
|
||||
return $ foldl mulExprsInt elementSize dSizes
|
||||
where
|
||||
dSizes = [case d of
|
||||
-- Fixed dimension.
|
||||
|
@ -296,7 +297,7 @@ declareSizesArray = occamOnlyPass "Declare array-size arrays"
|
|||
-- Destination has one free dimension, so we need to compute
|
||||
-- it.
|
||||
BIOneFree destSize n ->
|
||||
let newDim = A.Dimension $ divExprs srcSize destSize
|
||||
let newDim = A.Dimension $ divExprsInt srcSize destSize
|
||||
ds' = replaceAt n newDim ds in
|
||||
makeSizeSpec m [e | A.Dimension e <- ds']
|
||||
|
||||
|
@ -451,7 +452,7 @@ simplifySlices = occamOnlyPass "Simplify array slices"
|
|||
limit <- case d of
|
||||
A.Dimension n -> return n
|
||||
A.UnknownDimension -> return $ A.ExprVariable m $ specificDimSize 0 v
|
||||
return (A.SubscriptedVariable m (A.SubscriptFromFor m' check from (A.Dyadic m A.Subtr limit from)) v)
|
||||
return (A.SubscriptedVariable m (A.SubscriptFromFor m' check from (subExprsInt limit from)) v)
|
||||
doVariable v = return v
|
||||
|
||||
-- | Finds all processes that have a MOBILE parameter passed in Abbrev mode, and
|
||||
|
|
|
@ -101,7 +101,6 @@ cgenOps = GenOps {
|
|||
genDecl = cgenDecl,
|
||||
genDeclaration = cgenDeclaration,
|
||||
genDirectedVariable = cgenDirectedVariable,
|
||||
genDyadic = cgenDyadic,
|
||||
genExpression = cgenExpression,
|
||||
genFlatArraySize = cgenFlatArraySize,
|
||||
genForwardDeclaration = cgenForwardDeclaration,
|
||||
|
@ -121,7 +120,6 @@ cgenOps = GenOps {
|
|||
genLiteralRepr = cgenLiteralRepr,
|
||||
genMissing = cgenMissing,
|
||||
genMissingC = (\x -> x >>= cgenMissing),
|
||||
genMonadic = cgenMonadic,
|
||||
genOutput = cgenOutput,
|
||||
genOutputCase = cgenOutputCase,
|
||||
genOutputItem = cgenOutputItem,
|
||||
|
@ -933,8 +931,6 @@ cgenArraySubscript check v es
|
|||
|
||||
--{{{ expressions
|
||||
cgenExpression :: A.Expression -> CGen ()
|
||||
cgenExpression (A.Monadic m op e) = call genMonadic m op e
|
||||
cgenExpression (A.Dyadic m op e f) = call genDyadic m op e f
|
||||
cgenExpression (A.MostPos m t) = call genTypeSymbol "mostpos" t
|
||||
cgenExpression (A.MostNeg m t) = call genTypeSymbol "mostneg" t
|
||||
--cgenExpression (A.SizeType m t)
|
||||
|
@ -998,12 +994,6 @@ cgenFuncMonadic m s e
|
|||
genMeta m
|
||||
tell [")"]
|
||||
|
||||
cgenMonadic :: Meta -> A.MonadicOp -> A.Expression -> CGen ()
|
||||
cgenMonadic m A.MonadicSubtr e = call genFuncMonadic m "negate" e
|
||||
cgenMonadic _ A.MonadicMinus e = call genSimpleMonadic "-" e
|
||||
cgenMonadic _ A.MonadicBitNot e = call genSimpleMonadic "~" e
|
||||
cgenMonadic _ A.MonadicNot e = call genSimpleMonadic "!" e
|
||||
|
||||
cgenSimpleDyadic :: String -> A.Expression -> A.Expression -> CGen ()
|
||||
cgenSimpleDyadic s e f
|
||||
= do tell ["("]
|
||||
|
@ -1023,30 +1013,6 @@ cgenFuncDyadic m s e f
|
|||
tell [", "]
|
||||
genMeta m
|
||||
tell [")"]
|
||||
|
||||
cgenDyadic :: Meta -> A.DyadicOp -> A.Expression -> A.Expression -> CGen ()
|
||||
cgenDyadic m A.Add e f = call genFuncDyadic m "add" e f
|
||||
cgenDyadic m A.Subtr e f = call genFuncDyadic m "subtr" e f
|
||||
cgenDyadic m A.Mul e f = call genFuncDyadic m "mul" e f
|
||||
cgenDyadic m A.Div e f = call genFuncDyadic m "div" e f
|
||||
cgenDyadic m A.Rem e f = call genFuncDyadic m "rem" e f
|
||||
cgenDyadic m A.Plus e f = call genFuncDyadic m "plus" e f
|
||||
cgenDyadic m A.Minus e f = call genFuncDyadic m "minus" e f
|
||||
cgenDyadic m A.Times e f = call genFuncDyadic m "times" e f
|
||||
cgenDyadic m A.LeftShift e f = call genFuncDyadic m "lshift" e f
|
||||
cgenDyadic m A.RightShift e f = call genFuncDyadic m "rshift" e f
|
||||
cgenDyadic _ A.BitAnd e f = call genSimpleDyadic "&" e f
|
||||
cgenDyadic _ A.BitOr e f = call genSimpleDyadic "|" e f
|
||||
cgenDyadic _ A.BitXor e f = call genSimpleDyadic "^" e f
|
||||
cgenDyadic _ A.And e f = call genSimpleDyadic "&&" e f
|
||||
cgenDyadic _ A.Or e f = call genSimpleDyadic "||" e f
|
||||
cgenDyadic _ A.Eq e f = call genSimpleDyadic "==" e f
|
||||
cgenDyadic _ A.NotEq e f = call genSimpleDyadic "!=" e f
|
||||
cgenDyadic _ A.Less e f = call genSimpleDyadic "<" e f
|
||||
cgenDyadic _ A.More e f = call genSimpleDyadic ">" e f
|
||||
cgenDyadic _ A.LessEq e f = call genSimpleDyadic "<=" e f
|
||||
cgenDyadic _ A.MoreEq e f = call genSimpleDyadic ">=" e f
|
||||
cgenDyadic _ A.Concat e f = call genListConcat e f
|
||||
--}}}
|
||||
|
||||
cgenListConcat :: A.Expression -> A.Expression -> CGen ()
|
||||
|
|
|
@ -139,7 +139,6 @@ data GenOps = GenOps {
|
|||
-- The Bool indicates whether the declaration is inside a record (True) or not (False).
|
||||
genDeclaration :: Level -> A.Type -> A.Name -> Bool -> CGen (),
|
||||
genDirectedVariable :: Meta -> A.Type -> CGen () -> A.Direction -> CGen (),
|
||||
genDyadic :: Meta -> A.DyadicOp -> A.Expression -> A.Expression -> CGen (),
|
||||
genExpression :: A.Expression -> CGen (),
|
||||
genFlatArraySize :: [A.Dimension] -> CGen (),
|
||||
genForwardDeclaration :: A.Specification -> CGen(),
|
||||
|
@ -161,7 +160,6 @@ data GenOps = GenOps {
|
|||
genLiteralRepr :: A.LiteralRepr -> A.Type -> CGen (),
|
||||
genMissing :: String -> CGen (),
|
||||
genMissingC :: CGen String -> CGen (),
|
||||
genMonadic :: Meta -> A.MonadicOp -> A.Expression -> CGen (),
|
||||
-- | Generates an output statement.
|
||||
genOutput :: A.Variable -> [(A.Type, A.OutputItem)] -> CGen (),
|
||||
-- | Generates an output statement for a tagged protocol.
|
||||
|
|
|
@ -681,7 +681,7 @@ cppgetCType m t am | isChan t
|
|||
= do ct <- call getCType m t A.Original
|
||||
return $ Template "tockSendableArray"
|
||||
[Left ct
|
||||
,Right $ foldl1 (A.Dyadic m A.Mul) [n | A.Dimension n <- ds]
|
||||
,Right $ foldl1 mulExprsInt [n | A.Dimension n <- ds]
|
||||
]
|
||||
cppTypeInsideChannel t = call getCType m t A.Original
|
||||
cppgetCType m (A.List t) am
|
||||
|
|
Loading…
Reference in New Issue
Block a user