Fixed the Rain passes so the the alphabet test case now works (at least)

This commit is contained in:
Neil Brown 2008-05-17 20:51:42 +00:00
parent 1e5268dea5
commit e53fda754e
2 changed files with 16 additions and 24 deletions

View File

@ -21,6 +21,7 @@ module RainPasses where
import Control.Monad.State import Control.Monad.State
import Data.Generics import Data.Generics
import Data.List
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Maybe import Data.Maybe
@ -42,44 +43,38 @@ rainPasses = makePassesDep' ((== FrontendRain) . csFrontend)
,("Dummy Rain pass", return, [], [Prop.retypesChecked]) ,("Dummy Rain pass", return, [], [Prop.retypesChecked])
,("Resolve Int -> Int64", transformInt, [], [Prop.noInt]) ,("Resolve Int -> Int64", transformInt, [], [Prop.noInt])
,("Uniquify variable declarations, record declared types and resolve variable names", ,("Uniquify variable declarations, record declared types and resolve variable names",
uniquifyAndResolveVars, [Prop.noInt], namesDone) uniquifyAndResolveVars, [Prop.noInt], Prop.agg_namesDone \\ [Prop.inferredTypesRecorded])
-- ,("Fold all constant expressions", constantFoldPass, [Prop.noInt] ++ namesDone, [Prop.constantsFolded, Prop.constantsChecked]) ,("Fold all constant expressions", constantFoldPass, [Prop.noInt] ++ Prop.agg_namesDone
,("Type Checking", performTypeUnification, [Prop.noInt] ++ namesDone, ++ Prop.agg_typesDone, [Prop.constantsFolded, Prop.constantsChecked])
typesDone) ,("Type Checking", performTypeUnification, [Prop.noInt] ++ Prop.agg_namesDone,
Prop.agg_typesDone)
-- ,("Annotate integer literal types", annotateIntLiteralTypes, [Prop.noInt] ++ namesDone, [Prop.intLiteralsInBounds]) -- ,("Annotate integer literal types", annotateIntLiteralTypes, [Prop.noInt] ++ namesDone, [Prop.intLiteralsInBounds])
-- ,("Annotate list literal and range types", annotateListLiteralTypes, -- ,("Annotate list literal and range types", annotateListLiteralTypes,
-- namesDone ++ [Prop.noInt, Prop.intLiteralsInBounds], [Prop.listsGivenType]) -- namesDone ++ [Prop.noInt, Prop.intLiteralsInBounds], [Prop.listsGivenType])
,("Record inferred name types in dictionary", recordInfNameTypes, ,("Record inferred name types in dictionary", recordInfNameTypes,
namesDone ++ [Prop.intLiteralsInBounds, Prop.listsGivenType], [Prop.inferredTypesRecorded]) Prop.agg_namesDone \\ [Prop.inferredTypesRecorded], [Prop.inferredTypesRecorded])
,("Check types in expressions",checkExpressionTypes, namesDone ++ [Prop.noInt, Prop.constantsFolded, Prop.intLiteralsInBounds, Prop.inferredTypesRecorded], [Prop.expressionTypesChecked]) -- ,("Check types in expressions",checkExpressionTypes, namesDone ++ [Prop.noInt, Prop.constantsFolded, Prop.intLiteralsInBounds, Prop.inferredTypesRecorded], [Prop.expressionTypesChecked])
-- ,("Check types in assignments", checkAssignmentTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked]) -- ,("Check types in assignments", checkAssignmentTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked])
-- ,("Check types in if/while conditions",checkConditionalTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked]) -- ,("Check types in if/while conditions",checkConditionalTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked])
-- ,("Check types in input/output",checkCommTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked]) -- ,("Check types in input/output",checkCommTypes, typesDone ++ [Prop.expressionTypesChecked], [Prop.processTypesChecked])
,("Check parameters in process calls", matchParamPass, typesDone, [Prop.processTypesChecked, -- ,("Check parameters in process calls", matchParamPass, typesDone, [Prop.processTypesChecked,
Prop.functionTypesChecked]) -- Prop.functionTypesChecked])
,("Find and tag the main function", findMain, namesDone, [Prop.mainTagged]) ,("Find and tag the main function", findMain, Prop.agg_namesDone, [Prop.mainTagged])
,("Convert seqeach/pareach loops over ranges into simple replicated SEQ/PAR", ,("Convert seqeach/pareach loops over ranges into simple replicated SEQ/PAR",
transformEachRange, typesDone ++ [Prop.constantsFolded], [Prop.eachRangeTransformed]) transformEachRange, Prop.agg_typesDone ++ [Prop.constantsFolded], [Prop.eachRangeTransformed])
,("Pull up foreach-expressions", pullUpForEach, ,("Pull up foreach-expressions", pullUpForEach,
typesDone ++ [Prop.constantsFolded], Prop.agg_typesDone ++ [Prop.constantsFolded],
[Prop.eachTransformed]) [Prop.eachTransformed])
,("Convert simple Rain range constructors into more general array constructors",transformRangeRep, typesDone ++ [Prop.eachRangeTransformed], [Prop.rangeTransformed]) ,("Convert simple Rain range constructors into more general array constructors",transformRangeRep, Prop.agg_typesDone ++ [Prop.eachRangeTransformed], [Prop.rangeTransformed])
,("Transform Rain functions into the occam form",checkFunction, typesDone, []) ,("Transform Rain functions into the occam form",checkFunction, Prop.agg_typesDone, [])
--TODO add an export property. Maybe check other things too (lack of comms etc -- but that could be combined with occam?) --TODO add an export property. Maybe check other things too (lack of comms etc -- but that could be combined with occam?)
,("Pull up par declarations", pullUpParDeclarations, [], [Prop.rainParDeclarationsPulledUp]) ,("Pull up par declarations", pullUpParDeclarations, [], [Prop.rainParDeclarationsPulledUp])
] ]
where
namesDone :: [Property]
namesDone = [Prop.declaredNamesResolved, Prop.declarationTypesRecorded, Prop.declarationsUnique]
typesDone :: [Property]
typesDone = namesDone ++ [Prop.inferredTypesRecorded]
-- | A pass that transforms all instances of 'A.Int' into 'A.Int64' -- | A pass that transforms all instances of 'A.Int' into 'A.Int64'
transformInt :: Data t => t -> PassM t transformInt :: Data t => t -> PassM t

View File

@ -121,10 +121,7 @@ recordInfNameTypes = everywhereM (mkM recordInfNameTypes')
where where
recordInfNameTypes' :: A.Replicator -> PassM A.Replicator recordInfNameTypes' :: A.Replicator -> PassM A.Replicator
recordInfNameTypes' input@(A.ForEach m n e) recordInfNameTypes' input@(A.ForEach m n e)
= do arrType <- astTypeOf e = do let innerT = A.UnknownVarType $ Left n
innerT <- case arrType of
A.List t -> return t
_ -> diePC m $ formatCode "Cannot do a foreach loop over a non-list type: %" arrType
defineName n A.NameDef {A.ndMeta = m, A.ndName = A.nameName n, A.ndOrigName = A.nameName n, defineName n A.NameDef {A.ndMeta = m, A.ndName = A.nameName n, A.ndOrigName = A.nameName n,
A.ndNameType = A.VariableName, A.ndType = (A.Declaration m innerT), A.ndNameType = A.VariableName, A.ndType = (A.Declaration m innerT),
A.ndAbbrevMode = A.Abbrev, A.ndPlacement = A.Unplaced} A.ndAbbrevMode = A.Abbrev, A.ndPlacement = A.Unplaced}