Merged latest patches from trunk into Polyplate
This commit is contained in:
parent
9069282ca2
commit
e409b15b58
|
@ -241,6 +241,8 @@ instance ShowOccam A.Type where
|
||||||
showOccamM A.Any = tell ["ANY"]
|
showOccamM A.Any = tell ["ANY"]
|
||||||
showOccamM (A.Timer _) = tell ["TIMER"]
|
showOccamM (A.Timer _) = tell ["TIMER"]
|
||||||
showOccamM A.Time = tell ["TIME"]
|
showOccamM A.Time = tell ["TIME"]
|
||||||
|
showOccamM A.Infer = tell ["inferred type"]
|
||||||
|
showOccamM A.Barrier = tell ["BARRIER"]
|
||||||
showOccamM (A.UnknownVarType _ en)
|
showOccamM (A.UnknownVarType _ en)
|
||||||
= do tell ["(inferred type for: "]
|
= do tell ["(inferred type for: "]
|
||||||
either showName (tell . (:[]) . show) en
|
either showName (tell . (:[]) . show) en
|
||||||
|
|
|
@ -56,8 +56,10 @@ instance Warn PassM where
|
||||||
-- against AST fragments of other types as well.
|
-- against AST fragments of other types as well.
|
||||||
type PassType t = t -> PassM t
|
type PassType t = t -> PassM t
|
||||||
|
|
||||||
type PassOnOps ops
|
type PassOnOpsM m ops
|
||||||
= (PolyplateM t ops () PassM, PolyplateM t () ops PassM) => Pass t
|
= (PolyplateM t ops () m, PolyplateM t () ops m) => Pass t
|
||||||
|
|
||||||
|
type PassOnOps ops = PassOnOpsM PassM ops
|
||||||
|
|
||||||
type CheckOnOps ops
|
type CheckOnOps ops
|
||||||
= (PolyplateSpine t ops () (PassM ())) => Pass t
|
= (PolyplateSpine t ops () (PassM ())) => Pass t
|
||||||
|
|
|
@ -19,7 +19,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
-- | Traversal strategies over the AST and other data types. This is now mainly
|
-- | Traversal strategies over the AST and other data types. This is now mainly
|
||||||
-- a collection of extra Tock-specific utilities that go on top of Polyplate
|
-- a collection of extra Tock-specific utilities that go on top of Polyplate
|
||||||
module Traversal (
|
module Traversal (
|
||||||
TransformM, Transform, TransformStructured, TransformStructured'
|
TransformM, Transform, TransformStructured, TransformStructured', TransformStructuredM'
|
||||||
, CheckM, Check
|
, CheckM, Check
|
||||||
, ExtOpMP, ExtOpMS, ExtOpMSP, extOpMS, PassOnStruct, PassASTOnStruct
|
, ExtOpMP, ExtOpMS, ExtOpMSP, extOpMS, PassOnStruct, PassASTOnStruct
|
||||||
, ExtOpQS, extOpQS
|
, ExtOpQS, extOpQS
|
||||||
|
@ -205,3 +205,7 @@ type TransformStructured ops
|
||||||
type TransformStructured' ops
|
type TransformStructured' ops
|
||||||
= (PolyplateM (A.Structured t) () ops PassM
|
= (PolyplateM (A.Structured t) () ops PassM
|
||||||
,PolyplateM (A.Structured t) ops () PassM , Data t) => Transform (A.Structured t)
|
,PolyplateM (A.Structured t) ops () PassM , Data t) => Transform (A.Structured t)
|
||||||
|
|
||||||
|
type TransformStructuredM' m ops
|
||||||
|
= (PolyplateM (A.Structured t) () ops m
|
||||||
|
,PolyplateM (A.Structured t) ops () m , Data t) => A.Structured t -> m (A.Structured t)
|
||||||
|
|
|
@ -20,7 +20,8 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
module SimplifyProcs (simplifyProcs, fixLowReplicators) where
|
module SimplifyProcs (simplifyProcs, fixLowReplicators) where
|
||||||
|
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Data.Generics
|
import Data.Generics (Data)
|
||||||
|
import Data.Maybe
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
|
|
||||||
import qualified AST as A
|
import qualified AST as A
|
||||||
|
@ -42,18 +43,23 @@ simplifyProcs =
|
||||||
, flattenAssign
|
, flattenAssign
|
||||||
]
|
]
|
||||||
|
|
||||||
|
type ForkM = StateT [A.Name] PassM
|
||||||
|
type ForkOps = ExtOpM ForkM (ExtOpMS ForkM BaseOp) A.Process
|
||||||
|
|
||||||
-- | Add an extra barrier parameter to every PROC for FORKING
|
-- | Add an extra barrier parameter to every PROC for FORKING
|
||||||
addForkNames :: Pass
|
addForkNames :: PassOnOpsM ForkM ForkOps
|
||||||
addForkNames = occamOnlyPass "Add FORK labels" [] []
|
addForkNames = occamOnlyPass "Add FORK labels" [] []
|
||||||
(flip evalStateT [] . recurse)
|
(flip evalStateT [] . recurse)
|
||||||
where
|
where
|
||||||
ops = baseOp `extOpS` doStructured `extOp` doProcess
|
ops :: ForkOps
|
||||||
|
ops = baseOp `extOpMS` (ops, doStructured) `extOpM` doProcess
|
||||||
|
|
||||||
recurse, descend :: Data a => a -> StateT [A.Name] PassM a
|
recurse :: RecurseM ForkM ForkOps
|
||||||
recurse = makeRecurse ops
|
recurse = makeRecurseM ops
|
||||||
descend = makeDescend ops
|
descend :: DescendM ForkM ForkOps
|
||||||
|
descend = makeDescendM ops
|
||||||
|
|
||||||
doProcess :: A.Process -> StateT [A.Name] PassM A.Process
|
doProcess :: A.Process -> ForkM A.Process
|
||||||
doProcess (A.Fork m Nothing p)
|
doProcess (A.Fork m Nothing p)
|
||||||
= do (f:_) <- get
|
= do (f:_) <- get
|
||||||
p' <- recurse p
|
p' <- recurse p
|
||||||
|
@ -67,7 +73,7 @@ addForkNames = occamOnlyPass "Add FORK labels" [] []
|
||||||
_ -> return $ A.ProcCall m n (A.ActualVariable (A.Variable m f) : as)
|
_ -> return $ A.ProcCall m n (A.ActualVariable (A.Variable m f) : as)
|
||||||
doProcess p = descend p
|
doProcess p = descend p
|
||||||
|
|
||||||
doStructured :: Data a => A.Structured a -> StateT [A.Name] PassM (A.Structured a)
|
doStructured :: TransformStructuredM' ForkM ForkOps
|
||||||
doStructured (A.Spec m spec@(A.Specification _ n (A.Forking _)) scope)
|
doStructured (A.Spec m spec@(A.Specification _ n (A.Forking _)) scope)
|
||||||
= do modify (n:)
|
= do modify (n:)
|
||||||
scope' <- recurse scope
|
scope' <- recurse scope
|
||||||
|
|
|
@ -46,9 +46,15 @@ resolveNamedTypes
|
||||||
(Prop.agg_namesDone
|
(Prop.agg_namesDone
|
||||||
++ [Prop.expressionTypesChecked, Prop.processTypesChecked])
|
++ [Prop.expressionTypesChecked, Prop.processTypesChecked])
|
||||||
[Prop.typesResolvedInAST, Prop.typesResolvedInState]
|
[Prop.typesResolvedInAST, Prop.typesResolvedInState]
|
||||||
(\t -> do get >>= resolve >>= put
|
(\t -> do get >>= resolve >>= flatten >>= put
|
||||||
resolve t)
|
resolve t >>= flatten)
|
||||||
where
|
where
|
||||||
resolve :: PassTypeOn A.Type
|
resolve :: PassTypeOn A.Type
|
||||||
resolve = applyTopDownM (underlyingType emptyMeta)
|
resolve = applyTopDownM (resolveUserType emptyMeta)
|
||||||
|
|
||||||
|
flatten :: PassTypeOn A.Type
|
||||||
|
flatten = applyBottomUpM doType
|
||||||
|
where
|
||||||
|
doType :: Transform A.Type
|
||||||
|
doType (A.Array dsA (A.Array dsB t)) = return $ A.Array (dsA++dsB) t
|
||||||
|
doType t = return t
|
||||||
|
|
Loading…
Reference in New Issue
Block a user