Changed the rain foreach-pass test to actually run the transformEach pass it was meant to be testing, and also got the transformEach test to compile

This commit is contained in:
Neil Brown 2007-08-16 13:16:04 +00:00
parent 2d7349eb5d
commit 3d1d5e35ef
2 changed files with 16 additions and 8 deletions

View File

@ -6,9 +6,12 @@ import qualified Data.Map as Map
import qualified AST as A import qualified AST as A
import TestUtil import TestUtil
import TreeUtil import TreeUtil
import RainPasses
import CompState
import Control.Monad.Error (runErrorT)
testEachPass0 :: Test testEachPass0 :: Test
testEachPass0 = TestCase $ assertPatternMatch "testEachPass0" exp orig testEachPass0 = TestCase $ assertPatternMatch "testEachPass0" exp (evalStateT (runErrorT (transformEach orig)) emptyState)
where where
orig = A.Seq m orig = A.Seq m
(A.Rep m (A.Rep m

View File

@ -1,6 +1,11 @@
module RainPasses where module RainPasses where
import TestUtil import TestUtil
import qualified AST as A
import Pass
import Data.Generics
import Types
import CompState
--TODO add passes for: --TODO add passes for:
-- Typing the variables -- Typing the variables
@ -11,25 +16,25 @@ rainPasses :: A.Process -> PassM A.Process
rainPasses = runPasses passes rainPasses = runPasses passes
where where
passes = passes =
[ ("Convert seqeach/pareach loops into classic replicated SEQ/PAR",transformEach) [ ("Convert seqeach/pareach loops into classic replicated SEQ/PAR",transformEach)
] ]
--TODO test this pass and then tidy it up --TODO test this pass and then tidy it up
transformEach :: Data t => t -> PassM t transformEach :: Data t => t -> PassM t
transformEach = everywhere (mkM transformEach') transformEach = everywhereM (mkM transformEach')
where where
transformEach' :: A.Structured -> A.Structured transformEach' :: A.Structured -> PassM A.Structured
transformEach' (A.Rep m (A.ForEach m' loopVar loopExp) s) transformEach' (A.Rep m (A.ForEach m' loopVar loopExp) s)
= do (spec,var) <- case loopExp of = do (spec,var) <- case loopExp of
(A.ExprVariable _ v) -> return (\x -> x,v) (A.ExprVariable _ v) -> return (\x -> x,v)
_ -> do t <- typeOfExpression loopExp _ -> do t <- typeOfExpression loopExp
spec@(A.Specification _ n' _) <- makeNonceIsExpr "loopVar" m t loopExp spec@(A.Specification _ n' _) <- makeNonceIsExpr "loopVar" m t loopExp
return (\x -> A.Specification m spec x,A.Variable m n') return (\x -> A.Spec m spec x,A.Variable m n')
--spec is a function A.Structured -> A.Structured, var is an A.Variable --spec is a function A.Structured -> A.Structured, var is an A.Variable
loopVarType <- typeOfVariable loopVar loopVarType <- typeOfName loopVar
loopIndex <- makeNonce "loopIndex" loopIndex <- makeNonce "loopIndex"
let newRep = A.For m' (simpleName loopIndex) (intLiteral 0) (A.SizeVariable m' var) 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 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')) return (spec (A.Rep m newRep s'))
transformEach' s = s transformEach' s = return s