module Language.Dung.AF
(
DungAF(..),
setAttacks, conflictFree, acceptable, f, admissible, unattacked, attacked,
groundedF, Status(..), grounded, groundedExt)
where
import Data.List (intersect, (\\))
data DungAF arg = AF [arg] [(arg, arg)]
deriving (Eq, Show)
setAttacks :: Eq arg => DungAF arg -> [arg] -> arg -> Bool
setAttacks (AF _ def) args arg
= or [b == arg | (a, b) <- def, a `elem` args]
conflictFree :: Eq arg => DungAF arg -> [arg] -> Bool
conflictFree (AF _ def) args
= null [(a,b) | (a, b) <- def, a `elem` args, b `elem` args]
acceptable :: Eq arg => DungAF arg -> arg -> [arg] -> Bool
acceptable af@(AF _ def) a args
= and [setAttacks af args b | (b, a') <- def, a == a']
f :: Eq arg => DungAF arg -> [arg] -> [arg]
f af@(AF args' _) args = [a | a <- args', acceptable af a args]
subset :: Eq a => [a] -> [a] -> Bool
xs `subset` ys = null (xs \\ ys)
admissible :: Eq arg => DungAF arg -> [arg] -> Bool
admissible af args = conflictFree af args && args `subset` f af args
groundedF :: Eq arg => ([arg] -> [arg]) -> [arg]
groundedF f = groundedF' f []
where groundedF' f args
| f args == args = args
| otherwise = groundedF' f (f args)
unattacked :: Eq arg => [arg] ->
DungAF arg -> arg -> Bool
unattacked outs (AF _ def) arg =
let attackers = [a | (a, b) <- def, arg == b]
in null (attackers \\ outs)
attacked :: Eq arg => [arg] ->
DungAF arg -> arg -> Bool
attacked ins (AF _ def) arg =
let attackers = [a | (a, b) <- def, arg == b]
in not (null (attackers `intersect` ins))
data Status = In | Out | Undecided
deriving (Eq, Show)
grounded :: Eq arg => DungAF arg -> [(arg, Status)]
grounded af@(AF args _) = grounded' [] [] args af
where
grounded' :: Eq a => [a] -> [a] ->
[a] -> DungAF a -> [(a, Status)]
grounded' ins outs [] _
= map (\ x -> (x, In)) ins
++ map (\ x -> (x, Out)) outs
grounded' ins outs args af =
let newIns = filter (unattacked outs af) args
newOuts = filter (attacked ins af) args
in if null (newIns ++ newOuts)
then map (\ x -> (x, In)) ins
++ map (\ x -> (x, Out)) outs
++ map (\ x -> (x, Undecided)) args
else grounded' (ins ++ newIns)
(outs ++ newOuts)
(args \\ (newIns ++ newOuts))
af
groundedExt :: Eq arg => DungAF arg -> [arg]
groundedExt af = [arg | (arg, In) <- grounded af]