module Language.Clafer.Intermediate.SimpleScopeAnalyzer (simpleScopeAnalysis) where
import Control.Applicative ((<$>))
import Control.Lens hiding (elements, assign)
import Data.Graph
import Data.List
import Data.Data.Lens (biplate)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.Ord
import Data.Ratio
import Prelude hiding (exp)
import Language.Clafer.Common
import Language.Clafer.Intermediate.Intclafer
simpleScopeAnalysis :: IModule -> [(String, Integer)]
simpleScopeAnalysis iModule@IModule{_mDecls = decls'} =
[(a, b) | (a, b) <- finalAnalysis, b /= 1]
where
uidClaferMap' = createUidIClaferMap iModule
findClafer :: UID -> IClafer
findClafer uid' = fromJust $ findIClafer uidClaferMap' uid'
finalAnalysis = Map.toList $ foldl analyzeComponent supersAndRefsAnalysis connectedComponents
upperCards u =
Map.findWithDefault (error $ "No upper cardinality for clafer named \"" ++ u ++ "\".") u upperCardsMap
upperCardsMap = Map.fromList [(_uid c, snd $ fromJust $ _card c) | c <- clafers]
supersAnalysis = foldl (analyzeSupers uidClaferMap' clafers) Map.empty decls'
supersAndRefsAnalysis = foldl (analyzeRefs uidClaferMap' clafers) supersAnalysis decls'
constraintAnalysis = analyzeConstraints constraints upperCards
(subclaferMap, parentMap) = analyzeHierarchy uidClaferMap' clafers
connectedComponents = analyzeDependencies uidClaferMap' clafers
clafers :: [ IClafer ]
clafers = universeOn biplate iModule
constraints = concatMap findConstraints decls'
lowerOrUpperFixedCard analysis' clafer =
maximum [cardLb, cardUb, lowFromConstraints, oneForStar, targetScopeForStar ]
where
Just (cardLb, cardUb) = _card clafer
oneForStar = if (cardLb == 0 && cardUb == 1) then 1 else 0
targetScopeForStar = if ((isJust $ _reference clafer) && cardUb == 1)
then case getReference clafer of
[ref'] -> Map.findWithDefault 1 (fromMaybe "unknown" $ _uid <$> findIClafer uidClaferMap' ref' ) analysis'
_ -> 0
else 0
lowFromConstraints = Map.findWithDefault 0 (_uid clafer) constraintAnalysis
analyzeComponent analysis' component =
case flattenSCC component of
[uid'] -> analyzeSingleton uid' analysis'
uids ->
foldr analyzeSingleton assume uids
where
assume = foldr (`Map.insert` 1) analysis' uids
where
analyzeSingleton uid' analysis'' = analyze analysis'' $ findClafer uid'
analyze :: Map String Integer -> IClafer -> Map String Integer
analyze analysis' clafer =
Map.insertWith max (_uid clafer) scope analysis'
where
scope
| _isAbstract clafer = sum subclaferScopes
| otherwise = parentScope * (lowerOrUpperFixedCard analysis' clafer)
subclaferScopes = map (findOrError " subclafer scope not found" analysis') subclafers
parentScope =
case parentMaybe of
Just parent'' -> findOrError " parent scope not found" analysis' parent''
Nothing -> rootScope
subclafers = Map.findWithDefault [] (_uid clafer) subclaferMap
parentMaybe = Map.lookup (_uid clafer) parentMap
rootScope = 1
findOrError message m key = Map.findWithDefault (error $ key ++ message) key m
analyzeSupers :: UIDIClaferMap -> [IClafer] -> Map String Integer -> IElement -> Map String Integer
analyzeSupers uidClaferMap' clafers analysis (IEClafer clafer) =
foldl (analyzeSupers uidClaferMap' clafers) analysis' (_elements clafer)
where
(Just (cardLb, cardUb)) = _card clafer
lowerOrFixedUpperBound = maximum [1, cardLb, cardUb ]
analysis' = if (isJust $ _reference clafer)
then analysis
else case (directSuper uidClaferMap' clafer) of
(Just c) -> Map.alter (incLB lowerOrFixedUpperBound) (_uid c) analysis
Nothing -> analysis
incLB lb' Nothing = Just lb'
incLB lb' (Just lb) = Just (lb + lb')
analyzeSupers _ _ analysis _ = analysis
analyzeRefs :: UIDIClaferMap -> [IClafer] -> Map String Integer -> IElement -> Map String Integer
analyzeRefs uidClaferMap' clafers analysis (IEClafer clafer) =
foldl (analyzeRefs uidClaferMap' clafers) analysis' (_elements clafer)
where
(Just (cardLb, cardUb)) = _card clafer
lowerOrFixedUpperBound = maximum [1, cardLb, cardUb]
analysis' = if (isJust $ _reference clafer)
then case (directSuper uidClaferMap' clafer) of
(Just c) -> Map.alter (maxLB lowerOrFixedUpperBound) (_uid c) analysis
Nothing -> analysis
else analysis
maxLB lb' Nothing = Just lb'
maxLB lb' (Just lb) = Just (max lb lb')
analyzeRefs _ _ analysis _ = analysis
analyzeConstraints :: [PExp] -> (String -> Integer) -> Map String Integer
analyzeConstraints constraints upperCards =
foldr analyzeConstraint Map.empty $ filter isOneOrSomeConstraint constraints
where
isOneOrSomeConstraint PExp{_exp = IDeclPExp{_quant = quant'}} =
case quant' of
IOne -> True
ISome -> True
_ -> False
isOneOrSomeConstraint _ = False
analyzeConstraint PExp{_exp = IDeclPExp{_oDecls = [], _bpexp = bpexp'}} analysis =
foldr atLeastOne analysis path'
where
path' = dropThisAndParent $ unfoldJoins bpexp'
atLeastOne = Map.insertWith max `flip` 1
analyzeConstraint PExp{_exp = IDeclPExp{_oDecls = decls'}} analysis =
foldr analyzeDecl analysis decls'
analyzeConstraint _ analysis = analysis
analyzeDecl IDecl{_isDisj = isDisj', _decls = decls', _body = body'} analysis =
foldr (uncurry insert') analysis $ zip path' scores
where
path' = dropThisAndParent $ unfoldJoins body'
minScope = if isDisj' then fromIntegral $ length decls' else 1
insert' = Map.insertWith max
scores = assign path' minScope
assign [] _ = [1]
assign (p : ps) score =
pScore : ps'
where
ps' = assign ps score
psScore = product $ ps'
pDesireScore = ceiling (score % psScore)
pMaxScore = upperCards p
pScore = min' pDesireScore pMaxScore
min' a b = if b == 1 then a else min a b
dropThisAndParent = dropWhile (== "parent") . dropWhile (== "this")
analyzeDependencies :: UIDIClaferMap -> [IClafer] -> [SCC String]
analyzeDependencies uidClaferMap' clafers = connComponents
where
connComponents = stronglyConnComp [(key, key, depends) | (key, depends) <- dependencyGraph]
dependencies = concatMap (dependency uidClaferMap') clafers
dependencyGraph = Map.toList $ Map.fromListWith (++) [(a, [b]) | (a, b) <- dependencies]
dependency :: UIDIClaferMap -> IClafer -> [(String, String)]
dependency uidClaferMap' clafer =
selfDependency : (maybeToList superDependency ++ childDependencies)
where
selfDependency = (_uid clafer, _uid clafer)
superDependency
| isNothing $ _super clafer = Nothing
| otherwise =
do
super' <- directSuper uidClaferMap' clafer
return (_uid super', _uid clafer)
childDependencies = [(_uid child, _uid clafer) | child <- childClafers clafer]
analyzeHierarchy :: UIDIClaferMap -> [IClafer] -> (Map String [String], Map String String)
analyzeHierarchy uidClaferMap' clafers =
foldl hierarchy (Map.empty, Map.empty) clafers
where
hierarchy (subclaferMap, parentMap) clafer = (subclaferMap', parentMap')
where
subclaferMap' =
case super' of
Just super'' -> Map.insertWith (++) (_uid super'') [_uid clafer] subclaferMap
Nothing -> subclaferMap
super' = directSuper uidClaferMap' clafer
parentMap' = foldr (flip Map.insert $ _uid clafer) parentMap (map _uid $ childClafers clafer)
directSuper :: UIDIClaferMap -> IClafer -> Maybe IClafer
directSuper uidClaferMap' clafer =
second $ findHierarchy getSuper uidClaferMap' clafer
where
second [] = Nothing
second [_] = Nothing
second (_:x:_) = Just x
findConstraints :: IElement -> [PExp]
findConstraints IEConstraint{_cpexp = c} = [c]
findConstraints (IEClafer clafer) = concatMap findConstraints (_elements clafer)
findConstraints _ = []
childClafers :: IClafer -> [IClafer]
childClafers clafer = clafer ^.. elements.traversed.iClafer
unfoldJoins :: PExp -> [String]
unfoldJoins pexp =
fromMaybe [] $ unfoldJoins' pexp
where
unfoldJoins' PExp{_exp = (IFunExp "." args)} =
return $ args >>= unfoldJoins
unfoldJoins' PExp{_exp = IClaferId{_sident = sident'}} =
return $ [sident']
unfoldJoins' _ =
fail "not a join"