{-# LANGUAGE DeriveDataTypeable #-} module DPM.Core.Conflicts ( Conflicts, PatchConflicts, emptyConflicts, addConflict, getConflicts, addConflictWithRepo, conflictsWithRepo ) where import qualified Data.List as List import Data.Data ( Data ) import Data.Typeable ( Typeable ) import DPM.Core.DataTypes ( PatchID ) data Conflicts a = Conflicts { c_pairs :: [(a,a)] , c_withRepo :: [a] } deriving (Eq,Ord,Show,Read,Data,Typeable) type PatchConflicts = Conflicts PatchID emptyConflicts :: Ord a => Conflicts a emptyConflicts = Conflicts [] [] addConflict :: Ord a => Conflicts a -> (a, a) -> Conflicts a addConflict c p = if p `elem` c_pairs c then c else c { c_pairs = (p : c_pairs c) } addConflictWithRepo :: Ord a => Conflicts a -> a -> Conflicts a addConflictWithRepo c x = if x `elem` c_withRepo c then c else c { c_withRepo = x : c_withRepo c } conflictsWithRepo :: Ord a => Conflicts a -> a -> Bool conflictsWithRepo c x = x `elem` c_withRepo c getConflicts :: Ord a => Conflicts a -> a -> [a] getConflicts c key = List.nub (worker (c_pairs c) []) where worker [] acc = reverse acc worker ((x,y):rest) acc = let acc1 = if x == key then y:acc else acc acc2 = if y == key then x:acc1 else acc1 in worker rest acc2