Overhauled the usage checker to use sets of Strings for recording the used variables
This commit is contained in:
parent
700ddf149e
commit
d38c2aef08
|
@ -85,7 +85,7 @@ data Direction =
|
||||||
| DirOutput -- ^ The output end.
|
| DirOutput -- ^ The output end.
|
||||||
| DirUnknown -- ^ Either direction; either this is a whole channel,
|
| DirUnknown -- ^ Either direction; either this is a whole channel,
|
||||||
-- or its direction is to be figured out later.
|
-- or its direction is to be figured out later.
|
||||||
deriving (Show, Eq, Typeable, Data)
|
deriving (Show, Eq, Ord, Typeable, Data)
|
||||||
|
|
||||||
-- | Attributes of the type of a channel.
|
-- | Attributes of the type of a channel.
|
||||||
data ChanAttributes = ChanAttributes {
|
data ChanAttributes = ChanAttributes {
|
||||||
|
|
|
@ -22,71 +22,117 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
-- the control-flow graph means that we only need to concentrate on each node that isn't nested.
|
-- the control-flow graph means that we only need to concentrate on each node that isn't nested.
|
||||||
module RainUsageCheck where
|
module RainUsageCheck where
|
||||||
|
|
||||||
|
import Control.Monad.Identity
|
||||||
import Data.Generics
|
import Data.Generics
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import qualified Data.Set as Set
|
||||||
|
|
||||||
import qualified AST as A
|
import qualified AST as A
|
||||||
|
import FlowGraph
|
||||||
|
|
||||||
--An obvious thing to do would be to hold these lists (of written/read variables respectively) instead as sets
|
-- In Rain, Deref can't nest with Dir in either way, so this doesn't need to be a recursive type:
|
||||||
--However, this would involve defining an ordering over A.Variable. This would be do-able for plain A.Variables,
|
data Var =
|
||||||
--but in order to define a proper ordering for subscripted variables, we would end up needing to provide an
|
Plain String
|
||||||
--ordering for A.Expression (and all its subtypes)! Therefore, they are kept simply as lists:
|
| Deref String
|
||||||
|
| Dir A.Direction String
|
||||||
|
deriving (Eq, Show, Ord)
|
||||||
|
|
||||||
|
data Vars = Vars {
|
||||||
|
maybeRead :: Set.Set Var,
|
||||||
|
maybeWritten :: Set.Set Var,
|
||||||
|
defWritten :: Set.Set Var,
|
||||||
|
used :: Set.Set Var -- e.g. channels, barriers
|
||||||
|
-- passed :: Set.Set String
|
||||||
|
}
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
type WrittenRead = ([A.Variable],[A.Variable])
|
emptyVars :: Vars
|
||||||
|
emptyVars = Vars Set.empty Set.empty Set.empty Set.empty
|
||||||
|
|
||||||
concatWR :: WrittenRead -> WrittenRead -> WrittenRead
|
readVars :: [Var] -> Vars
|
||||||
concatWR (w0,r0) (w1,r1) = (w0 ++ w1,r0 ++ r1)
|
readVars ss = Vars (Set.fromList ss) Set.empty Set.empty Set.empty
|
||||||
|
|
||||||
foldWR :: [WrittenRead] -> WrittenRead
|
writtenVars :: [Var] -> Vars
|
||||||
foldWR = foldl1 concatWR
|
writtenVars ss = Vars Set.empty (Set.fromList ss) (Set.fromList ss) Set.empty
|
||||||
|
|
||||||
removeDupWR :: WrittenRead -> WrittenRead
|
vars :: [Var] -> [Var] -> [Var] -> [Var] -> Vars
|
||||||
removeDupWR (w,r) = (nub w,nub r)
|
vars mr mw dw u = Vars (Set.fromList mr) (Set.fromList mw) (Set.fromList dw) (Set.fromList u)
|
||||||
|
|
||||||
|
unionVars :: Vars -> Vars -> Vars
|
||||||
|
unionVars (Vars mr mw dw u) (Vars mr' mw' dw' u') = Vars (mr `Set.union` mr') (mw `Set.union` mw') (dw `Set.union` dw') (u `Set.union` u')
|
||||||
|
|
||||||
|
foldUnionVars :: [Vars] -> Vars
|
||||||
|
foldUnionVars = foldl unionVars emptyVars
|
||||||
|
|
||||||
|
nameToString :: A.Name -> String
|
||||||
|
nameToString = A.nameName
|
||||||
|
|
||||||
--Gets the (written,read) variables of a piece of an occam program:
|
--Gets the (written,read) variables of a piece of an occam program:
|
||||||
|
|
||||||
--For subscripted variables used as Lvalues , e.g. a[b] it should return a[b] as written-to and b as read
|
--For subscripted variables used as Lvalues , e.g. a[b] it should return a[b] as written-to and b as read
|
||||||
--For subscripted variables used as expressions, e.g. a[b] it should return a[b],b as read (with no written-to)
|
--For subscripted variables used as expressions, e.g. a[b] it should return a[b],b as read (with no written-to)
|
||||||
|
|
||||||
getVars :: Data t => t -> WrittenRead
|
getVarProc :: A.Process -> Vars
|
||||||
getVars
|
getVarProc (A.Assign _ vars expList)
|
||||||
= removeDupWR . (everything concatWR (([],[])
|
|
||||||
`mkQ` getVarProc
|
|
||||||
))
|
|
||||||
where
|
|
||||||
getVarProc :: A.Process -> WrittenRead
|
|
||||||
getVarProc (A.Assign _ vars expList)
|
|
||||||
--Join together:
|
--Join together:
|
||||||
= concatWR
|
= unionVars
|
||||||
--The written-to variables on the LHS:
|
--The written-to variables on the LHS:
|
||||||
(foldWR (map processVarW vars))
|
(foldUnionVars (map processVarW vars))
|
||||||
--All variables read on the RHS:
|
--All variables read on the RHS:
|
||||||
(everything concatWR (([],[]) `mkQ` getVarExp) expList)
|
(getVarExpList expList)
|
||||||
--TODO output input etc (all other processes that directly write to/read from variables)
|
--TODO output input etc (all other processes that directly write to/read from variables)
|
||||||
getVarProc _ = ([],[])
|
getVarProc _ = emptyVars
|
||||||
|
|
||||||
{-
|
{-
|
||||||
Near the beginning, this piece of code was too clever for itself and applied processVarW using "everything".
|
Near the beginning, this piece of code was too clever for itself and applied processVarW using "everything".
|
||||||
The problem with this is that given var@(A.SubscriptedVariable _ sub arrVar), the functions would be recursively
|
The problem with this is that given var@(A.SubscriptedVariable _ sub arrVar), the functions would be recursively
|
||||||
applied to sub and arrVar. processVarW should return var, but never the subscripts in sub; those subscripts are not written to!
|
applied to sub and arrVar. processVarW should return var as written to, but never the subscripts in sub; those subscripts are not written to!
|
||||||
|
|
||||||
Therefore processVarW must *not* be applied using the generics library, and instead should always be applied
|
Therefore processVarW must *not* be applied using the generics library, and instead should always be applied
|
||||||
directly to an A.Variable. Internally it uses the generics library to process the subscripts (using getVarExp)
|
directly to an A.Variable. Internally it uses the generics library to process the subscripts (using getVarExp)
|
||||||
-}
|
-}
|
||||||
|
|
||||||
--Pull out all the subscripts into the read category, but leave the given var in the written category:
|
--Pull out all the subscripts into the read category, but leave the given var in the written category:
|
||||||
processVarW :: A.Variable -> WrittenRead
|
processVarW :: A.Variable -> Vars
|
||||||
processVarW v@(A.Variable _ _) = ([v],[])
|
processVarW (A.Variable _ n) = writtenVars [Plain $ nameToString n]
|
||||||
processVarW v@(A.SubscriptedVariable _ s _) = concatWR ([v],[]) (everything concatWR (([],[]) `mkQ` getVarExp) s)
|
processVarW (A.DerefVariable _ (A.Variable _ n)) = writtenVars [Deref $ nameToString n]
|
||||||
|
--DirectedVariable illegal on the LHS of an assignment/RHS of an input:
|
||||||
|
processVarW _ = emptyVars
|
||||||
|
|
||||||
--Only need to deal with the two cases where we can see an A.Variable directly;
|
processVarR :: A.Variable -> Vars
|
||||||
--the generic recursion will take care of nested expressions, and even the expressions used as subscripts
|
processVarR (A.Variable _ n) = readVars [Plain $ nameToString n]
|
||||||
getVarExp :: A.Expression -> WrittenRead
|
processVarR (A.DirectedVariable _ dir (A.Variable _ n)) = readVars [Dir dir $ nameToString n]
|
||||||
getVarExp (A.SizeVariable _ v) = ([],[v])
|
processVarR (A.DerefVariable _ (A.Variable _ n)) = readVars [Deref $ nameToString n]
|
||||||
getVarExp (A.ExprVariable _ v) = ([],[v])
|
processVarR _ = emptyVars
|
||||||
getVarExp _ = ([],[])
|
|
||||||
|
getVarExpList :: A.ExpressionList -> Vars
|
||||||
|
getVarExpList (A.ExpressionList _ es) = foldUnionVars $ map getVarExp es
|
||||||
|
getVarExpList (A.FunctionCallList _ _ es) = foldUnionVars $ map getVarExp es --TODO record stuff in passed as well?
|
||||||
|
|
||||||
|
getVarExp :: A.Expression -> Vars
|
||||||
|
getVarExp = everything unionVars (emptyVars `mkQ` getVarExp')
|
||||||
|
where
|
||||||
|
--Only need to deal with the two cases where we can see an A.Variable directly;
|
||||||
|
--the generic recursion will take care of nested expressions, and even the expressions used as subscripts
|
||||||
|
getVarExp' :: A.Expression -> Vars
|
||||||
|
getVarExp' (A.SizeVariable _ v) = processVarR v
|
||||||
|
getVarExp' (A.ExprVariable _ v) = processVarR v
|
||||||
|
getVarExp' _ = emptyVars
|
||||||
|
|
||||||
|
getVarLabelFuncs :: GraphLabelFuncs Identity Vars
|
||||||
|
getVarLabelFuncs = GLF
|
||||||
|
{
|
||||||
|
labelExpression = return . getVarExp
|
||||||
|
,labelExpressionList = return . getVarExpList
|
||||||
|
,labelDummy = return . (const emptyVars)
|
||||||
|
,labelProcess = return . getVarProc
|
||||||
|
--TODO don't forget about the variables used as initialisers in declarations!
|
||||||
|
,labelScopeIn = return . (const emptyVars)
|
||||||
|
,labelScopeOut = return . (const emptyVars)
|
||||||
|
}
|
||||||
|
|
||||||
|
{-
|
||||||
|
|
||||||
|
|
||||||
-- I am not sure how you could build this out of the standard functions, so I built it myself
|
-- I am not sure how you could build this out of the standard functions, so I built it myself
|
||||||
|
@ -165,3 +211,4 @@ parUsageCheck proc
|
||||||
subscriptedArrays' :: A.Variable -> Maybe A.Variable
|
subscriptedArrays' :: A.Variable -> Maybe A.Variable
|
||||||
subscriptedArrays' (A.SubscriptedVariable _ _ v) = Just v
|
subscriptedArrays' (A.SubscriptedVariable _ _ v) = Just v
|
||||||
subscriptedArrays' _ = Nothing
|
subscriptedArrays' _ = Nothing
|
||||||
|
-}
|
||||||
|
|
Loading…
Reference in New Issue
Block a user