{-# OPTIONS_GHC -F -pgmF htfpp #-} module DPM.Core.ReverseDependencies where import qualified Data.Map as Map import Test.Framework import DPM.Core.DataTypes ( PatchID ) type Map = Map.Map data RevDeps a = RevDeps { rd_map :: Map a [a] } type PatchRevDeps = RevDeps PatchID getRevDeps :: Ord a => RevDeps a -> a -> [a] getRevDeps rd key = Map.findWithDefault [] key (rd_map rd) getMaxChainLen :: Ord a => RevDeps a -> a -> Int getMaxChainLen rd key = case Map.lookup key (rd_map rd) of Nothing -> 0 Just l -> 1 + maximum (map (getMaxChainLen rd) l) buildRevDeps :: Ord a => [(a, [a])] -> RevDeps a buildRevDeps list = RevDeps $ foldr add Map.empty list where add (x,ys) m0 = foldr (\y m -> Map.insertWith (++) y [x] m) m0 ys prop_hasMapping :: [(Int, [Int])] -> Bool prop_hasMapping list = let rd = buildRevDeps list in all (hasMapping rd) list where hasMapping rd (val, keys) = all (\k -> val `elem` getRevDeps rd k) keys