diff --git a/RainPassTest.hs b/RainPassTest.hs new file mode 100644 index 0000000..78492d2 --- /dev/null +++ b/RainPassTest.hs @@ -0,0 +1,50 @@ +module RainPassTest (tests) where + +import Test.HUnit +import Control.Monad.State as CSM +import qualified Data.Map as Map +import qualified AST as A +import TestUtil +import TreeUtil + +testEachPass0 :: Test +testEachPass0 = TestCase $ assertPatternMatch "testEachPass0" exp orig + where + orig = A.Seq m + (A.Rep m + (A.ForEach m (simpleName "c") (makeLiteralString "1")) + (A.OnlyP m (makeAssign (variable "c") (intLiteral 7))) + ) + exp = tag2 A.Seq DontCare + (tag3 A.Spec DontCare + (tag3 A.Specification DontCare listVar + (tag4 A.IsExpr DontCare A.ValAbbrev (A.Array [A.Dimension 1] A.Byte) listVar) + ) + (tag3 A.Rep DontCare + (tag4 A.For DontCare indexVar (intLiteral 0) (tag2 A.SizeExpr DontCare (tag2 A.ExprVariable DontCare listVar))) + (tag3 A.Spec DontCare + (tag3 A.Specification DontCare (simpleName "c") + (tag4 A.Is DontCare A.Abbrev A.Byte + (tag3 A.SubscriptedVariable DontCare + (tag2 A.Subscript DontCare (tag2 A.ExprVariable DontCare indexVar)) + listVar + ) + ) + ) + (A.OnlyP m (makeAssign (variable "c") (intLiteral 7))) + ) + ) + ) + indexVar = Named "indexVar" DontCare + listVar = Named "listVar" DontCare + + + +--Returns the list of tests: +tests :: Test +tests = TestList + [ + testEachPass0 + ] + + diff --git a/RainPasses.hs b/RainPasses.hs new file mode 100644 index 0000000..74596e1 --- /dev/null +++ b/RainPasses.hs @@ -0,0 +1,35 @@ +module RainPasses where + +import TestUtil + +--TODO add passes for: +-- Typing the variables +-- Resolving (and uniquifying) names + + +rainPasses :: A.Process -> PassM A.Process +rainPasses = runPasses passes + where + passes = + [ ("Convert seqeach/pareach loops into classic replicated SEQ/PAR",transformEach) + ] + +--TODO test this pass and then tidy it up +transformEach :: Data t => t -> PassM t +transformEach = everywhere (mkM transformEach') + where + transformEach' :: A.Structured -> A.Structured + transformEach' (A.Rep m (A.ForEach m' loopVar loopExp) s) + = do (spec,var) <- case loopExp of + (A.ExprVariable _ v) -> return (\x -> x,v) + _ -> do t <- typeOfExpression loopExp + spec@(A.Specification _ n' _) <- makeNonceIsExpr "loopVar" m t loopExp + return (\x -> A.Specification m spec x,A.Variable m n') + --spec is a function A.Structured -> A.Structured, var is an A.Variable + + loopVarType <- typeOfVariable loopVar + loopIndex <- makeNonce "loopIndex" + let newRep = A.For m' (simpleName loopIndex) (intLiteral 0) (A.SizeVariable m' var) + let s' = A.Spec m' (A.Specification m' loopVar (A.Is m' A.Abbrev loopVarType (A.SubscriptedVariable m' (A.Subscript m' (A.ExprVariable m' (variable loopIndex))) var) )) s + return (spec (A.Rep m newRep s')) + transformEach' s = s diff --git a/TestMain.hs b/TestMain.hs index 4db0354..fcccaa6 100644 --- a/TestMain.hs +++ b/TestMain.hs @@ -1,9 +1,10 @@ module TestMain () where -import qualified RainParseTest as RP -import qualified UsageCheckTest as UC +import qualified RainParseTest (tests) +import qualified RainPassTest (tests) +import qualified UsageCheckTest (tests) import Test.HUnit main :: IO () -main = do runTestTT $ TestList [RP.tests,UC.tests] +main = do runTestTT $ TestList [RainParseTest.tests,RainPassTest.tests,UsageCheckTest.tests] return ()