module Swish.Ruleset
( Ruleset(..), RulesetMap
, makeRuleset, getRulesetNamespace, getRulesetAxioms, getRulesetRules
, getRulesetAxiom, getRulesetRule
, getContextAxiom, getMaybeContextAxiom
, getContextRule, getMaybeContextRule
)
where
import Swish.Namespace (Namespace, ScopedName)
import Swish.Rule (Formula(..), Rule(..))
import Data.Maybe (fromMaybe, listToMaybe, mapMaybe)
import qualified Data.Map as M
data Ruleset ex = Ruleset
{ forall ex. Ruleset ex -> Namespace
rsNamespace :: Namespace
, forall ex. Ruleset ex -> [Formula ex]
rsAxioms :: [Formula ex]
, forall ex. Ruleset ex -> [Rule ex]
rsRules :: [Rule ex]
}
instance Eq (Ruleset ex) where
Ruleset ex
r1 == :: Ruleset ex -> Ruleset ex -> Bool
== Ruleset ex
r2 = forall ex. Ruleset ex -> Namespace
rsNamespace Ruleset ex
r1 forall a. Eq a => a -> a -> Bool
== forall ex. Ruleset ex -> Namespace
rsNamespace Ruleset ex
r2
type RulesetMap ex = M.Map Namespace (Ruleset ex)
makeRuleset :: Namespace -> [Formula ex] -> [Rule ex] -> Ruleset ex
makeRuleset :: forall ex. Namespace -> [Formula ex] -> [Rule ex] -> Ruleset ex
makeRuleset Namespace
nsp [Formula ex]
fms [Rule ex]
rls = Ruleset
{ rsNamespace :: Namespace
rsNamespace = Namespace
nsp
, rsAxioms :: [Formula ex]
rsAxioms = [Formula ex]
fms
, rsRules :: [Rule ex]
rsRules = [Rule ex]
rls
}
getRulesetNamespace :: Ruleset ex -> Namespace
getRulesetNamespace :: forall ex. Ruleset ex -> Namespace
getRulesetNamespace = forall ex. Ruleset ex -> Namespace
rsNamespace
getRulesetAxioms :: Ruleset ex -> [Formula ex]
getRulesetAxioms :: forall ex. Ruleset ex -> [Formula ex]
getRulesetAxioms = forall ex. Ruleset ex -> [Formula ex]
rsAxioms
getRulesetRules :: Ruleset ex -> [Rule ex]
getRulesetRules :: forall ex. Ruleset ex -> [Rule ex]
getRulesetRules = forall ex. Ruleset ex -> [Rule ex]
rsRules
getRulesetAxiom :: ScopedName -> Ruleset ex -> Maybe (Formula ex)
getRulesetAxiom :: forall ex. ScopedName -> Ruleset ex -> Maybe (Formula ex)
getRulesetAxiom ScopedName
nam Ruleset ex
rset =
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ScopedName
nam forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\Formula ex
f -> (forall ex. Formula ex -> ScopedName
formName Formula ex
f, Formula ex
f)) (forall ex. Ruleset ex -> [Formula ex]
rsAxioms Ruleset ex
rset)
getRulesetRule :: ScopedName -> Ruleset ex -> Maybe (Rule ex)
getRulesetRule :: forall ex. ScopedName -> Ruleset ex -> Maybe (Rule ex)
getRulesetRule ScopedName
nam Ruleset ex
rset =
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ScopedName
nam forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\Rule ex
r -> (forall ex. Rule ex -> ScopedName
ruleName Rule ex
r, Rule ex
r)) (forall ex. Ruleset ex -> [Rule ex]
rsRules Ruleset ex
rset)
getContextAxiom ::
ScopedName
-> Formula ex
-> [Ruleset ex]
-> Formula ex
getContextAxiom :: forall ex. ScopedName -> Formula ex -> [Ruleset ex] -> Formula ex
getContextAxiom ScopedName
nam Formula ex
def [Ruleset ex]
rsets = forall a. a -> Maybe a -> a
fromMaybe Formula ex
def (forall ex. ScopedName -> [Ruleset ex] -> Maybe (Formula ex)
getMaybeContextAxiom ScopedName
nam [Ruleset ex]
rsets)
getMaybeContextAxiom ::
ScopedName
-> [Ruleset ex]
-> Maybe (Formula ex)
getMaybeContextAxiom :: forall ex. ScopedName -> [Ruleset ex] -> Maybe (Formula ex)
getMaybeContextAxiom ScopedName
nam [Ruleset ex]
rsets =
forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall ex. ScopedName -> Ruleset ex -> Maybe (Formula ex)
getRulesetAxiom ScopedName
nam) [Ruleset ex]
rsets
getContextRule ::
ScopedName
-> Rule ex
-> [Ruleset ex]
-> Rule ex
getContextRule :: forall ex. ScopedName -> Rule ex -> [Ruleset ex] -> Rule ex
getContextRule ScopedName
nam Rule ex
def [Ruleset ex]
rsets = forall a. a -> Maybe a -> a
fromMaybe Rule ex
def (forall ex. ScopedName -> [Ruleset ex] -> Maybe (Rule ex)
getMaybeContextRule ScopedName
nam [Ruleset ex]
rsets)
getMaybeContextRule ::
ScopedName
-> [Ruleset ex]
-> Maybe (Rule ex)
getMaybeContextRule :: forall ex. ScopedName -> [Ruleset ex] -> Maybe (Rule ex)
getMaybeContextRule ScopedName
nam [Ruleset ex]
rsets =
forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall ex. ScopedName -> Ruleset ex -> Maybe (Rule ex)
getRulesetRule ScopedName
nam) [Ruleset ex]
rsets