Fixed the listify function, especially for the C backend, so that the ordering is what we want, regardless of whether it makes sense

This commit is contained in:
Neil Brown 2009-04-13 22:40:25 +00:00
parent d36503e15d
commit c2b31d3c78
6 changed files with 19 additions and 16 deletions

View File

@ -182,11 +182,11 @@ cgenTopLevel headerName s
= A.nameName n `elem` (csOriginalTopLevelProcs cs)
tellToHeader $ sequence_ $ map (call genForwardDeclaration)
(listifyTopDown isTopLevelSpec s)
(reverse $ listifyDepth isTopLevelSpec s)
-- Things like lifted wrapper_procs we still need to forward-declare,
-- but we do it in the C file, not in the header:
sequence_ $ map (call genForwardDeclaration)
(listifyTopDown (not . isTopLevelSpec) s)
(reverse $ listifyDepth (not . isTopLevelSpec) s)
tell ["#include \"", dropPath headerName, "\"\n"]

View File

@ -144,11 +144,11 @@ cppgenTopLevel headerName s
= A.nameName n `elem` (csOriginalTopLevelProcs cs)
tellToHeader $ sequence_ $ map (call genForwardDeclaration)
(listifyTopDown isTopLevelSpec s)
(reverse $ listifyDepth isTopLevelSpec s)
-- Things like lifted wrapper_procs we still need to forward-declare,
-- but we do it in the C file, not in the header:
sequence_ $ map (call genForwardDeclaration)
(listifyTopDown (\sp@(A.Specification _ n _)
(reverse $ listifyDepth (\sp@(A.Specification _ n _)
-> not (isTopLevelSpec sp)
&& A.nameName n `notElem` map fst (csExternals cs)) s)

View File

@ -107,12 +107,12 @@ followBK = map followBK'
next = Set.fromList $ map Var $ concatMap allVarsInBK bk
allVarsInBK :: BackgroundKnowledge -> [A.Variable]
allVarsInBK (Equal a b) = listifyTopDown (const True) a
++ listifyTopDown (const True) b
allVarsInBK (LessThanOrEqual a b) = listifyTopDown (const True) a
++ listifyTopDown (const True) b
allVarsInBK (RepBoundsIncl v a b) = v : (listifyTopDown (const True) a
++ listifyTopDown (const True) b)
allVarsInBK (Equal a b) = listifyDepth (const True) a
++ listifyDepth (const True) b
allVarsInBK (LessThanOrEqual a b) = listifyDepth (const True) a
++ listifyDepth (const True) b
allVarsInBK (RepBoundsIncl v a b) = v : (listifyDepth (const True) a
++ listifyDepth (const True) b)
data And a = And [a]
data Or a = Or [a]

View File

@ -204,7 +204,7 @@ findConstraints graph startNode
processNode (n, e) nodeVal curAgg = case fmap getNodeData $ lab graph n of
Just u ->
let overlapsWithWritten e = not $ null $ intersect
(listifyTopDown (const True) $ snd e)
(listifyDepth (const True) $ snd e)
[v | Var v <- Map.keys $ writtenVars $ nodeVars u]
valFilt = filter (not . overlapsWithWritten) $
nub $ nodeVal ++ (case e of

View File

@ -86,9 +86,12 @@ makeCheckM ops f v
-- the item in the list, False to drop it), finds all items of type \"s\" in some
-- larger item (of type \"t\") that satisfy this function, listed in depth-first
-- order.
listifyTopDown :: (PolyplateM t (OneOpM (State [s]) s) () (State [s])
,PolyplateM s () (OneOpM (State [s]) s) (State [s])) => (s -> Bool) -> t -> [s]
listifyTopDown qf = flip execState [] . applyBottomUpM qf'
listifyDepth :: (PolyplateM t (OneOpM (State [s]) s) () (State [s])
,PolyplateM s () (OneOpM (State [s]) s) (State [s])) => (s -> Bool) -> t -> [s]
-- We use applyBottomUp because we are prepending to the list. If we prepend from
-- the bottom up, that's the same as appending from the top down, which is what
-- this function is meant to be doing.
listifyDepth qf = flip execState [] . applyBottomUpM qf'
where
qf' x = if qf x then modify (x:) >> return x else return x

View File

@ -263,7 +263,7 @@ abbrevCheckPass
checkNotWritten (A.Variable m n) "VAL-abbreviated variable % written-to inside the scope of the abbreviation"
sequence_ [checkNotWritten v
"Abbreviated variable % used inside the scope of the abbreviation"
| A.ExprVariable _ v <- listifyTopDown (const True) e]
| A.ExprVariable _ v <- listifyDepth (const True) e]
pop
return s
doStructured s = descend s
@ -288,7 +288,7 @@ abbrevCheckPass
checkAbbreved v@(A.Variable {}) msg = checkNone v msg
checkAbbreved v@(A.DirectedVariable {}) msg = checkNone v msg
checkAbbreved (A.SubscriptedVariable _ sub v) msg
= sequence_ [checkNotWritten subV msg | subV <- listifyTopDown (const True) sub]
= sequence_ [checkNotWritten subV msg | subV <- listifyDepth (const True) sub]
checkNone :: A.Variable -> String -> StateT [Map.Map Var Bool] PassM ()
checkNone v msg