aboutsummaryrefslogtreecommitdiff
path: root/LifetimeAnalysis.hs
diff options
context:
space:
mode:
Diffstat (limited to 'LifetimeAnalysis.hs')
-rw-r--r--LifetimeAnalysis.hs17
1 files changed, 8 insertions, 9 deletions
diff --git a/LifetimeAnalysis.hs b/LifetimeAnalysis.hs
index aaf0c30..a421383 100644
--- a/LifetimeAnalysis.hs
+++ b/LifetimeAnalysis.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE ScopedTypeVariables #-}
-module LifetimeAnalysis(fullLifetimeAnalysis, lifetimeAnalysis, Access(..), unAccess) where
+module LifetimeAnalysis(fullLifetimeAnalysis, lifetimeAnalysis, Access(..), unAccess, BB) where
import Data.List
import Data.Maybe
@@ -36,20 +36,19 @@ markLive :: forall a. (Eq a, Ord a) => (BB a, DUIO a) -> [[a]]
markLive ((inaccs, _), duio) = init $ go fullaccs 0 (ins duio)
where
fullaccs = inaccs ++ [map Read (outs duio)]
- allvars = nub $ concatMap (map unAccess) fullaccs
- lastreads = Map.fromList $ map (\v -> (v, lastReadOf v)) allvars
- lastReadOf v = fromMaybe (-1) $ fmap ((length fullaccs - 1) -) $
- findIndex (Read v `elem`) (reverse fullaccs)
+ hasReadBeforeWrite _ [] = False
+ hasReadBeforeWrite t (acl : rest)
+ | Read t `elem` acl = True
+ | Write t `elem` acl = False
+ | otherwise = hasReadBeforeWrite t rest
go :: (Eq a, Ord a) => [[Access a]] -> Int -> [a] -> [[a]]
go [] _ _ = []
go (acl : rest) i lives =
let (ws, rs) = partitionAccess acl
- newlives = union rs $ flip filter (union ws lives) $ \v -> case Map.lookup v lastreads of
- Nothing -> False
- Just j -> j > i
- in lives : go rest (i+1) newlives
+ newlives = union rs $ flip filter (union ws lives) $ \v -> hasReadBeforeWrite v rest
+ in newlives : go rest (i+1) newlives
analysisIterator :: (Eq a, Ord a) => [(DUIO a, [Int])] -> [(DUIO a, [Int])]
analysisIterator toplist = map updateIns $ map updateOuts (zip toplist [0..])