Tweaked various code in the common and checks directory to work with the new step count in the For replicator
This commit is contained in:
parent
a68c871329
commit
594d7ef242
|
@ -449,7 +449,7 @@ makeEquations accesses bound
|
|||
rs' = zip (repeat AARead) rs
|
||||
|
||||
makeRepVarEq :: ((A.Name, A.Replicator), Bool) -> StateT VarMap (Either String) (A.Variable, EqualityConstraintEquation, EqualityConstraintEquation)
|
||||
makeRepVarEq ((varName, A.For m from for), _)
|
||||
makeRepVarEq ((varName, A.For m from for _), _)
|
||||
= do from' <- makeSingleEq from "replication start"
|
||||
upper <- makeSingleEq (A.Dyadic m A.Subtr (A.Dyadic m A.Add for from) (makeConstant m 1)) "replication count"
|
||||
return (A.Variable m varName, from', upper)
|
||||
|
@ -470,7 +470,7 @@ makeEquations accesses bound
|
|||
-- | Turns all instances of the variable from the given replicator into their primed version in the given expression
|
||||
mirrorFlaggedVars :: [FlattenedExp] -> ((A.Name, A.Replicator),Bool) -> StateT [(CoeffIndex,CoeffIndex)] (StateT VarMap (Either String)) [FlattenedExp]
|
||||
mirrorFlaggedVars exp (_,False) = return exp
|
||||
mirrorFlaggedVars exp ((varName, A.For m from for), True)
|
||||
mirrorFlaggedVars exp ((varName, A.For m from for _), True)
|
||||
= do varIndexes <- lift $ seqPair (varIndex (Scale 1 (A.ExprVariable emptyMeta var,0)), varIndex (Scale 1 (A.ExprVariable emptyMeta var,1)))
|
||||
modify (varIndexes :)
|
||||
return $ setIndexVar var 1 exp
|
||||
|
|
|
@ -471,7 +471,7 @@ testMakeEquations = TestLabel "testMakeEquations" $ TestList
|
|||
testRep' (ind, problems, (repName, repFrom, repFor), exprs, upperBound) =
|
||||
TestCase $ assertEquivalentProblems ("testMakeEquations " ++ show ind)
|
||||
(map (\((a0,a1),b,c,d) -> ((lookup exprs a0, lookup exprs a1), b, makeConsistent c d)) problems)
|
||||
=<< (checkRight $ makeEquations (RepParItem (simpleName "i", A.For emptyMeta repFrom repFor) $
|
||||
=<< (checkRight $ makeEquations (RepParItem (simpleName "i", A.For emptyMeta repFrom repFor (makeConstant emptyMeta 1)) $
|
||||
makeParItems [Map.fromList [(UsageCheckUtils.Var $ variable "i",
|
||||
[RepBoundsIncl (variable "i") repFrom (subOne $ addExprs repFrom repFor)])]] exprs) upperBound)
|
||||
|
||||
|
|
|
@ -124,7 +124,7 @@ addBK mp mp2 g nid n = fmap ((,) $ (map Map.fromList $ productN $ conBK ++
|
|||
--TODO only really need consider the connected nodes...
|
||||
|
||||
mkBK :: (A.Name, A.Replicator) -> [(Var, [BackgroundKnowledge])]
|
||||
mkBK (n, A.For _ low count) = [(Var v, bk)]
|
||||
mkBK (n, A.For _ low count _) = [(Var v, bk)]
|
||||
where
|
||||
m = A.nameMeta n
|
||||
v = A.Variable m n
|
||||
|
|
|
@ -239,7 +239,8 @@ getVarFormals m = mapUnionVars (getVarFormal m)
|
|||
getVarFormal m (A.Formal _ _ n) = processVarW (A.Variable m n) Nothing
|
||||
|
||||
getVarRepExp :: A.Replicator -> Vars
|
||||
getVarRepExp (A.For _ e0 e1) = getVarExp e0 `unionVars` getVarExp e1
|
||||
getVarRepExp (A.For _ e0 e1 e2) = getVarExp e0 `unionVars` getVarExp e1 `unionVars`
|
||||
getVarExp e2
|
||||
getVarRepExp (A.ForEach _ e) = getVarExp e
|
||||
|
||||
getVarAlternative :: A.Alternative -> Vars
|
||||
|
|
|
@ -584,7 +584,8 @@ instance ShowOccam A.Alternative where
|
|||
occamOutdent
|
||||
|
||||
instance ShowOccam A.Replicator where
|
||||
showOccamM (A.For _ start count) = tell [" = "] >> showOccamM start >> tell [" FOR "] >> showOccamM count
|
||||
showOccamM (A.For _ start count step) = tell [" = "] >> showOccamM start >> tell [" FOR "] >> showOccamM count
|
||||
>> tell [" STEP "] >> showOccamM step
|
||||
showOccamM (A.ForEach _ e) = tell [" IN "] >> showOccamM e
|
||||
|
||||
instance ShowOccam A.Choice where
|
||||
|
@ -709,7 +710,7 @@ instance ShowRain A.Process where
|
|||
showRainM (A.Par _ A.PlacedPar str) = outerRain "placed par" str
|
||||
|
||||
instance ShowRain A.Replicator where
|
||||
showRainM (A.For _ start count) = tell [" = "] >> showRainM start >> tell [" for "] >> showRainM count
|
||||
showRainM (A.For _ start count _) = tell [" = "] >> showRainM start >> tell [" for "] >> showRainM count
|
||||
showRainM (A.ForEach _ e) = tell ["each ("] >> colon >> showRainM e
|
||||
|
||||
--TEMP:
|
||||
|
|
|
@ -235,7 +235,8 @@ makePar procList = A.Par emptyMeta A.PlainPar $ A.Several emptyMeta (map (A.Only
|
|||
-- | Wraps the given process in a replicated 'A.Par' of the form PAR i = 0 FOR 3.
|
||||
makeRepPar :: A.Process -> A.Process
|
||||
makeRepPar proc = A.Par emptyMeta A.PlainPar $ A.Spec emptyMeta
|
||||
(A.Specification emptyMeta (simpleName "i") (A.Rep emptyMeta (A.For emptyMeta (intLiteral 0) (intLiteral 3)))) (A.Only emptyMeta proc)
|
||||
(A.Specification emptyMeta (simpleName "i") (A.Rep emptyMeta (A.For emptyMeta (intLiteral 0) (intLiteral 3)
|
||||
(intLiteral 1)))) (A.Only emptyMeta proc)
|
||||
|
||||
-- | Creates an assignment to the given 'A.Variable' from the given 'A.Expression.'
|
||||
makeAssign :: A.Variable -> A.Expression -> A.Process
|
||||
|
|
|
@ -100,7 +100,7 @@ typeOfSpec st
|
|||
A.IsChannelArray _ t _ -> return $ Just t
|
||||
A.Retypes _ _ t _ -> return $ Just t
|
||||
A.RetypesExpr _ _ t _ -> return $ Just t
|
||||
A.Rep _ (A.For _ _ e) -> astTypeOf e >>* Just
|
||||
A.Rep _ (A.For _ _ e _) -> astTypeOf e >>* Just
|
||||
A.Rep _ (A.ForEach _ e) -> do t <- astTypeOf e
|
||||
case t of
|
||||
A.List t' -> return $ Just t'
|
||||
|
@ -651,7 +651,7 @@ bytesInType _ = return $ BIUnknown
|
|||
|
||||
-- | Get the number of items a replicator produces.
|
||||
countReplicator :: A.Replicator -> A.Expression
|
||||
countReplicator (A.For _ _ count) = count
|
||||
countReplicator (A.For _ _ count _) = count
|
||||
|
||||
-- | Get the number of items in a Structured as an expression.
|
||||
countStructured :: Data a => A.Structured a -> A.Expression
|
||||
|
|
|
@ -84,7 +84,7 @@ sm11 = A.Skip m11
|
|||
|
||||
rep :: Data a => Meta -> A.Structured a -> A.Structured a
|
||||
rep m = A.Spec mU (A.Specification mU (simpleName "i") (A.Rep m (A.For m undefined
|
||||
undefined)))
|
||||
undefined undefined)))
|
||||
|
||||
-- | Shows a graph as a node and edge list.
|
||||
showGraph :: (Graph g, Show a, Show b) => g a b -> String
|
||||
|
@ -495,8 +495,8 @@ genElem2 f m = comb2 f (genMeta m)
|
|||
genElem3 :: (Meta -> a0 -> a1 -> b) -> Meta -> GenL a0 -> GenL a1 -> GenL b
|
||||
genElem3 f m = comb3 f (genMeta m)
|
||||
|
||||
--genElem4 :: (Meta -> a0 -> a1 -> a2 -> b) -> Meta -> GenL a0 -> GenL a1 -> GenL a2 -> GenL b
|
||||
--genElem4 f m = comb4 f (genMeta m)
|
||||
genElem4 :: (Meta -> a0 -> a1 -> a2 -> b) -> Meta -> GenL a0 -> GenL a1 -> GenL a2 -> GenL b
|
||||
genElem4 f m = comb4 f (genMeta m)
|
||||
|
||||
-- | A helper function for turning any item that can't be replaced into a GenL form (esp.
|
||||
-- for use as a parameter of genElemN).
|
||||
|
@ -525,13 +525,13 @@ comb3 func list0 list1 list2 = (liftM3 (,,)) list0 list1 list2 >>* product3 >>*
|
|||
process3 :: ([Meta], a0) -> ([Meta], a1) -> ([Meta],a2) -> ([Meta],b)
|
||||
process3 (keys0, val0) (keys1, val1) (keys2, val2) = (keys0++keys1++keys2, func val0 val1 val2)
|
||||
|
||||
{-
|
||||
|
||||
comb4 :: forall a0 a1 a2 a3 b. (a0 -> a1 -> a2 -> a3 -> b) -> GenL a0 -> GenL a1 -> GenL a2 -> GenL a3 -> GenL b
|
||||
comb4 func list0 list1 list2 list3 = (liftM4 (,,,)) list0 list1 list2 list3 >>* product4 >>* map (uncurry4 process4)
|
||||
where
|
||||
process4 :: ([Meta], a0) -> ([Meta], a1) -> ([Meta],a2) -> ([Meta],a3) -> ([Meta],b)
|
||||
process4 (keys0, val0) (keys1, val1) (keys2, val2) (keys3, val3) = (keys0++keys1++keys2++keys3, func val0 val1 val2 val3)
|
||||
-}
|
||||
|
||||
|
||||
-- | Wrapper for Quickcheck.
|
||||
-- In order to stop conflict with Quickcheck's in-built rules for things such as pairs
|
||||
|
@ -684,7 +684,7 @@ genOption' :: (Int, Int -> GenL A.Option)
|
|||
genOption' = (1, genOption)
|
||||
|
||||
genReplicator :: GenL A.Replicator
|
||||
genReplicator = nextIdT >>* makeMeta' >>= \m -> genElem3 A.For m genExpression genExpression
|
||||
genReplicator = nextIdT >>* makeMeta' >>= \m -> genElem4 A.For m genExpression genExpression genExpression
|
||||
|
||||
class ReplicatorAnnotation a where
|
||||
replicatorItem :: (Int, Int -> GenL a) -> Maybe (Int, Int -> GenL (A.Structured a))
|
||||
|
|
Loading…
Reference in New Issue
Block a user