tock-mirror/backends/BackendPasses.hs
Neil Brown 8d95b65f00 Added support for the new AlternativeWait guards to the C backend
This was not as straightforward as the C++ backend.  CIF has no capability for supporting waiting *for* a specified time as an ALT guard; only waiting until (AFTER, in occam) a specified time.  This is further complicated by the fact that when you disable an ALT timer guard in CIF, you have to be able to supply the timeout value that you waited on in the enable sequence.

Therefore, I added a pass that transforms all WaitFor guards into WaitUntil guards, by declaring nonce time variables, getting the time, and adding on the delay that we want to wait for; these actions occur just before the ALT.

This new pass is in the new BackendPasses module, into which I also moved the identifyParProcs pass.  I also wrote tests for my new pass that live in the new BackendPassesTest module.
2007-09-27 11:48:04 +00:00

71 lines
2.7 KiB
Haskell

{-
Tock: a compiler for parallel languages
Copyright (C) 2007 University of Kent
This program is free software; you can redistribute it and/or modify it
under the terms of the GNU General Public License as published by the
Free Software Foundation, either version 2 of the License, or (at your
option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
General Public License for more details.
You should have received a copy of the GNU General Public License along
with this program. If not, see <http://www.gnu.org/licenses/>.
-}
-- | Passes associated with the backends
module BackendPasses where
import Control.Monad.State
import Data.Generics
import qualified Data.Set as Set
import qualified AST as A
import CompState
import Pass
-- | Identify processes that we'll need to compute the stack size of.
identifyParProcs :: Pass
identifyParProcs = everywhereM (mkM doProcess)
where
doProcess :: A.Process -> PassM A.Process
doProcess p@(A.Par _ _ s) = findProcs s >> return p
doProcess p = return p
findProcs :: A.Structured -> PassM ()
findProcs (A.Rep _ _ s) = findProcs s
findProcs (A.Spec _ _ s) = findProcs s
findProcs (A.ProcThen _ _ s) = findProcs s
findProcs (A.Several _ ss) = sequence_ $ map findProcs ss
findProcs (A.OnlyP _ (A.ProcCall _ n _))
= modify (\cs -> cs { csParProcs = Set.insert n (csParProcs cs) })
transformWaitFor :: Data t => t -> PassM t
transformWaitFor = everywhereM (mkM doAlt)
where
doAlt :: A.Process -> PassM A.Process
doAlt a@(A.Alt m pri s)
= do (a',(specs,code)) <- runStateT (everywhereM (mkM doWaitFor) a) ([],[])
if (null specs && null code)
then return a
else return $ A.Seq m $ foldr addSpec (A.Several m (code ++ [A.OnlyP m a'])) specs
doAlt p = return p
addSpec :: (A.Structured -> A.Structured) -> A.Structured -> A.Structured
addSpec spec inner = spec inner
doWaitFor :: A.Alternative -> StateT ([A.Structured -> A.Structured], [A.Structured]) PassM A.Alternative
doWaitFor a@(A.AlternativeWait m A.WaitFor e p)
= do (specs, init) <- get
id <- lift $ makeNonce "waitFor"
let n = (A.Name m A.VariableName id)
let var = A.Variable m n
put (specs ++ [A.Spec m (A.Specification m n (A.Declaration m A.Time))],
init ++ [A.OnlyP m $ A.GetTime m var, A.OnlyP m $ A.Assign m [var] $ A.ExpressionList m [A.Dyadic m A.Plus (A.ExprVariable m var) e]])
return $ A.AlternativeWait m A.WaitUntil (A.ExprVariable m var) p
doWaitFor a = return a