{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Swish.RDF.Proof
( RDFProof, RDFProofStep
, makeRDFProof, makeRDFProofStep
, makeRdfInstanceEntailmentRule
, makeRdfSubgraphEntailmentRule
, makeRdfSimpleEntailmentRule )
where
import Swish.GraphClass (Label(..), LDGraph(..))
import Swish.Namespace (ScopedName)
import Swish.Proof (Proof(..), Step(..))
import Swish.Rule (Expression(..), Rule(..))
import Swish.VarBinding (makeVarBinding)
import Swish.RDF.Graph (RDFLabel(..), RDFGraph, fmapNSGraph)
import Swish.RDF.Graph (merge, allLabels, remapLabelList)
import Swish.RDF.Query (rdfQueryInstance, rdfQuerySubs)
import Swish.RDF.Ruleset (RDFFormula, RDFRule, RDFRuleset)
import Swish.Utils.ListHelpers (flist)
import Data.List (subsequences)
#if (!defined(__GLASGOW_HASKELL__)) || (__GLASGOW_HASKELL__ < 710)
import Data.Monoid (Monoid(..))
#endif
import qualified Data.Map as M
import qualified Data.Set as S
instance (LDGraph lg lb, Eq (lg lb)) => Expression (lg lb) where
isValid :: lg lb -> Bool
isValid = Set (Arc lb) -> Bool
forall a. Set a -> Bool
S.null (Set (Arc lb) -> Bool) -> (lg lb -> Set (Arc lb)) -> lg lb -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. lg lb -> Set (Arc lb)
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs
type RDFProof = Proof RDFGraph
type RDFProofStep = Step RDFGraph
makeRDFProofStep ::
RDFRule
-> [RDFFormula]
-> RDFFormula
-> RDFProofStep
makeRDFProofStep :: RDFRule -> [RDFFormula] -> RDFFormula -> RDFProofStep
makeRDFProofStep RDFRule
rul [RDFFormula]
ants RDFFormula
con = Step :: forall ex. Rule ex -> [Formula ex] -> Formula ex -> Step ex
Step
{ stepRule :: RDFRule
stepRule = RDFRule
rul
, stepAnt :: [RDFFormula]
stepAnt = [RDFFormula]
ants
, stepCon :: RDFFormula
stepCon = RDFFormula
con
}
makeRDFProof ::
[RDFRuleset]
-> RDFFormula
-> RDFFormula
-> [RDFProofStep]
-> RDFProof
makeRDFProof :: [RDFRuleset]
-> RDFFormula -> RDFFormula -> [RDFProofStep] -> RDFProof
makeRDFProof [RDFRuleset]
rsets RDFFormula
base RDFFormula
goal [RDFProofStep]
steps = Proof :: forall ex.
[Ruleset ex] -> Formula ex -> Formula ex -> [Step ex] -> Proof ex
Proof
{ proofContext :: [RDFRuleset]
proofContext = [RDFRuleset]
rsets
, proofInput :: RDFFormula
proofInput = RDFFormula
base
, proofResult :: RDFFormula
proofResult = RDFFormula
goal
, proofChain :: [RDFProofStep]
proofChain = [RDFProofStep]
steps
}
makeRdfInstanceEntailmentRule ::
ScopedName
-> [RDFLabel]
-> RDFRule
makeRdfInstanceEntailmentRule :: ScopedName -> [RDFLabel] -> RDFRule
makeRdfInstanceEntailmentRule ScopedName
name [RDFLabel]
vocab = RDFRule
newrule
where
newrule :: RDFRule
newrule = Rule :: forall ex.
ScopedName
-> ([ex] -> [ex])
-> (ex -> [[ex]])
-> ([ex] -> ex -> Bool)
-> Rule ex
Rule
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [RDFGraph] -> [RDFGraph]
fwdApply = [RDFLabel] -> [RDFGraph] -> [RDFGraph]
rdfInstanceEntailFwdApply [RDFLabel]
vocab
, bwdApply :: RDFGraph -> [[RDFGraph]]
bwdApply = [RDFLabel] -> RDFGraph -> [[RDFGraph]]
rdfInstanceEntailBwdApply [RDFLabel]
vocab
, checkInference :: [RDFGraph] -> RDFGraph -> Bool
checkInference = [RDFGraph] -> RDFGraph -> Bool
rdfInstanceEntailCheckInference
}
rdfInstanceEntailFwdApply :: [RDFLabel] -> [RDFGraph] -> [RDFGraph]
rdfInstanceEntailFwdApply :: [RDFLabel] -> [RDFGraph] -> [RDFGraph]
rdfInstanceEntailFwdApply [RDFLabel]
vocab [RDFGraph]
ante =
let
mergeGraph :: RDFGraph
mergeGraph = if [RDFGraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RDFGraph]
ante then RDFGraph
forall a. Monoid a => a
mempty
else (RDFGraph -> RDFGraph -> RDFGraph) -> [RDFGraph] -> RDFGraph
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 RDFGraph -> RDFGraph -> RDFGraph
forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [RDFGraph]
ante
nonvarNodes :: [RDFLabel]
nonvarNodes = [RDFLabel]
vocab
varNodes :: [RDFLabel]
varNodes = Set RDFLabel -> [RDFLabel]
forall a. Set a -> [a]
S.toList (Set RDFLabel -> [RDFLabel]) -> Set RDFLabel -> [RDFLabel]
forall a b. (a -> b) -> a -> b
$ (RDFLabel -> Bool) -> RDFGraph -> Set RDFLabel
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels RDFLabel -> Bool
forall lb. Label lb => lb -> Bool
labelIsVar RDFGraph
mergeGraph
mapList :: [(RDFLabel, RDFLabel)]
mapList = [RDFLabel] -> [RDFLabel] -> [(RDFLabel, RDFLabel)]
forall lb. Label lb => [lb] -> [lb] -> [(lb, lb)]
remapLabelList [RDFLabel]
nonvarNodes [RDFLabel]
varNodes
mapSubLists :: [[(RDFLabel, RDFLabel)]]
mapSubLists = ([[(RDFLabel, RDFLabel)]] -> [[(RDFLabel, RDFLabel)]]
forall a. [a] -> [a]
tail ([[(RDFLabel, RDFLabel)]] -> [[(RDFLabel, RDFLabel)]])
-> ([(RDFLabel, RDFLabel)] -> [[(RDFLabel, RDFLabel)]])
-> [(RDFLabel, RDFLabel)]
-> [[(RDFLabel, RDFLabel)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(RDFLabel, RDFLabel)] -> [[(RDFLabel, RDFLabel)]]
forall a. [a] -> [[a]]
subsequences) [(RDFLabel, RDFLabel)]
mapList
mapGr :: [(k, k)] -> NSGraph k -> NSGraph k
mapGr [(k, k)]
ls = (k -> k) -> NSGraph k -> NSGraph k
forall lb. Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph
(\k
l -> k -> k -> Map k k -> k
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault k
l k
l
([(k, k)] -> Map k k
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(k, k)]
ls))
in
[RDFGraph -> RDFGraph] -> RDFGraph -> [RDFGraph]
forall a b. [a -> b] -> a -> [b]
flist (([(RDFLabel, RDFLabel)] -> RDFGraph -> RDFGraph)
-> [[(RDFLabel, RDFLabel)]] -> [RDFGraph -> RDFGraph]
forall a b. (a -> b) -> [a] -> [b]
map [(RDFLabel, RDFLabel)] -> RDFGraph -> RDFGraph
forall k. Ord k => [(k, k)] -> NSGraph k -> NSGraph k
mapGr [[(RDFLabel, RDFLabel)]]
mapSubLists) RDFGraph
mergeGraph
rdfInstanceEntailBwdApply :: [RDFLabel] -> RDFGraph -> [[RDFGraph]]
rdfInstanceEntailBwdApply :: [RDFLabel] -> RDFGraph -> [[RDFGraph]]
rdfInstanceEntailBwdApply [RDFLabel]
vocab RDFGraph
cons =
let
varNodes :: [RDFLabel]
varNodes = Set RDFLabel -> [RDFLabel]
forall a. Set a -> [a]
S.toList (Set RDFLabel -> [RDFLabel]) -> Set RDFLabel -> [RDFLabel]
forall a b. (a -> b) -> a -> b
$ (RDFLabel -> Bool) -> RDFGraph -> Set RDFLabel
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels RDFLabel -> Bool
forall lb. Label lb => lb -> Bool
labelIsVar RDFGraph
cons
varBindings :: [VarBinding RDFLabel RDFLabel]
varBindings = ([RDFLabel] -> VarBinding RDFLabel RDFLabel)
-> [[RDFLabel]] -> [VarBinding RDFLabel RDFLabel]
forall a b. (a -> b) -> [a] -> [b]
map ([(RDFLabel, RDFLabel)] -> VarBinding RDFLabel RDFLabel
forall a b. (Ord a, Ord b) => [(a, b)] -> VarBinding a b
makeVarBinding ([(RDFLabel, RDFLabel)] -> VarBinding RDFLabel RDFLabel)
-> ([RDFLabel] -> [(RDFLabel, RDFLabel)])
-> [RDFLabel]
-> VarBinding RDFLabel RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RDFLabel] -> [RDFLabel] -> [(RDFLabel, RDFLabel)]
forall a b. [a] -> [b] -> [(a, b)]
zip [RDFLabel]
varNodes) [[RDFLabel]]
vocSequences
vocSequences :: [[RDFLabel]]
vocSequences = Int -> [RDFLabel] -> [[RDFLabel]]
forall a. Int -> [a] -> [[a]]
powerSequencesLen ([RDFLabel] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [RDFLabel]
varNodes) [RDFLabel]
vocab
in
[ [VarBinding RDFLabel RDFLabel] -> RDFGraph -> [RDFGraph]
rdfQuerySubs [VarBinding RDFLabel RDFLabel
v] RDFGraph
cons | VarBinding RDFLabel RDFLabel
v <- [VarBinding RDFLabel RDFLabel]
varBindings ]
rdfInstanceEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfInstanceEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfInstanceEntailCheckInference [RDFGraph]
ante RDFGraph
cons =
let
mante :: RDFGraph
mante = if [RDFGraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RDFGraph]
ante then RDFGraph
forall a. Monoid a => a
mempty
else (RDFGraph -> RDFGraph -> RDFGraph) -> [RDFGraph] -> RDFGraph
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 RDFGraph -> RDFGraph -> RDFGraph
forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [RDFGraph]
ante
qvars :: [VarBinding RDFLabel RDFLabel]
qvars = RDFGraph -> RDFGraph -> [VarBinding RDFLabel RDFLabel]
rdfQueryInstance RDFGraph
cons RDFGraph
mante
bsubs :: [RDFGraph]
bsubs = [VarBinding RDFLabel RDFLabel] -> RDFGraph -> [RDFGraph]
rdfQuerySubs [VarBinding RDFLabel RDFLabel]
qvars RDFGraph
cons
in
RDFGraph -> [RDFGraph] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem RDFGraph
mante [RDFGraph]
bsubs
powerSeqBylen :: [a] -> [[a]] -> [[[a]]]
powerSeqBylen :: [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs [[a]]
ps = [[a]]
ps [[a]] -> [[[a]]] -> [[[a]]]
forall a. a -> [a] -> [a]
: [a] -> [[a]] -> [[[a]]]
forall a. [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs ([a] -> [[a]] -> [[a]]
forall a. [a] -> [[a]] -> [[a]]
powerSeqNext [a]
rs [[a]]
ps)
powerSeqNext :: [a] -> [[a]] -> [[a]]
powerSeqNext :: [a] -> [[a]] -> [[a]]
powerSeqNext [a]
rs [[a]]
rss = [ a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
t | [a]
t <- [[a]]
rss, a
h <- [a]
rs ]
powerSequencesLen :: Int -> [a] -> [[a]]
powerSequencesLen :: Int -> [a] -> [[a]]
powerSequencesLen Int
len [a]
rs = [a] -> [[a]] -> [[[a]]]
forall a. [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs [[]] [[[a]]] -> Int -> [[a]]
forall a. [a] -> Int -> a
!! Int
len
makeRdfSubgraphEntailmentRule :: ScopedName -> RDFRule
makeRdfSubgraphEntailmentRule :: ScopedName -> RDFRule
makeRdfSubgraphEntailmentRule ScopedName
name = RDFRule
newrule
where
newrule :: RDFRule
newrule = Rule :: forall ex.
ScopedName
-> ([ex] -> [ex])
-> (ex -> [[ex]])
-> ([ex] -> ex -> Bool)
-> Rule ex
Rule
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [RDFGraph] -> [RDFGraph]
fwdApply = [RDFGraph] -> [RDFGraph]
rdfSubgraphEntailFwdApply
, bwdApply :: RDFGraph -> [[RDFGraph]]
bwdApply = [[RDFGraph]] -> RDFGraph -> [[RDFGraph]]
forall a b. a -> b -> a
const []
, checkInference :: [RDFGraph] -> RDFGraph -> Bool
checkInference = [RDFGraph] -> RDFGraph -> Bool
rdfSubgraphEntailCheckInference
}
rdfSubgraphEntailFwdApply :: [RDFGraph] -> [RDFGraph]
rdfSubgraphEntailFwdApply :: [RDFGraph] -> [RDFGraph]
rdfSubgraphEntailFwdApply [RDFGraph]
ante =
let
mergeGraph :: RDFGraph
mergeGraph = if [RDFGraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RDFGraph]
ante then RDFGraph
forall a. Monoid a => a
mempty
else (RDFGraph -> RDFGraph -> RDFGraph) -> [RDFGraph] -> RDFGraph
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 RDFGraph -> RDFGraph -> RDFGraph
forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [RDFGraph]
ante
in
([Arc RDFLabel] -> RDFGraph) -> [[Arc RDFLabel]] -> [RDFGraph]
forall a b. (a -> b) -> [a] -> [b]
map (RDFGraph -> ArcSet RDFLabel -> RDFGraph
forall (lg :: * -> *) lb.
LDGraph lg lb =>
lg lb -> ArcSet lb -> lg lb
setArcs RDFGraph
mergeGraph (ArcSet RDFLabel -> RDFGraph)
-> ([Arc RDFLabel] -> ArcSet RDFLabel)
-> [Arc RDFLabel]
-> RDFGraph
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Arc RDFLabel] -> ArcSet RDFLabel
forall a. Ord a => [a] -> Set a
S.fromList) ([[Arc RDFLabel]] -> [[Arc RDFLabel]]
forall a. [a] -> [a]
init ([[Arc RDFLabel]] -> [[Arc RDFLabel]])
-> [[Arc RDFLabel]] -> [[Arc RDFLabel]]
forall a b. (a -> b) -> a -> b
$ [[Arc RDFLabel]] -> [[Arc RDFLabel]]
forall a. [a] -> [a]
tail ([[Arc RDFLabel]] -> [[Arc RDFLabel]])
-> [[Arc RDFLabel]] -> [[Arc RDFLabel]]
forall a b. (a -> b) -> a -> b
$ [Arc RDFLabel] -> [[Arc RDFLabel]]
forall a. [a] -> [[a]]
subsequences ([Arc RDFLabel] -> [[Arc RDFLabel]])
-> [Arc RDFLabel] -> [[Arc RDFLabel]]
forall a b. (a -> b) -> a -> b
$ ArcSet RDFLabel -> [Arc RDFLabel]
forall a. Set a -> [a]
S.toList (ArcSet RDFLabel -> [Arc RDFLabel])
-> ArcSet RDFLabel -> [Arc RDFLabel]
forall a b. (a -> b) -> a -> b
$ RDFGraph -> ArcSet RDFLabel
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs RDFGraph
mergeGraph)
rdfSubgraphEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSubgraphEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSubgraphEntailCheckInference [RDFGraph]
ante RDFGraph
cons =
let
fullGraph :: RDFGraph
fullGraph = if [RDFGraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RDFGraph]
ante then RDFGraph
forall a. Monoid a => a
mempty
else (RDFGraph -> RDFGraph -> RDFGraph) -> [RDFGraph] -> RDFGraph
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 RDFGraph -> RDFGraph -> RDFGraph
forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [RDFGraph]
ante
in
RDFGraph -> ArcSet RDFLabel
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs RDFGraph
cons ArcSet RDFLabel -> ArcSet RDFLabel -> Bool
forall a. Ord a => Set a -> Set a -> Bool
`S.isSubsetOf` RDFGraph -> ArcSet RDFLabel
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs RDFGraph
fullGraph
makeRdfSimpleEntailmentRule :: ScopedName -> RDFRule
makeRdfSimpleEntailmentRule :: ScopedName -> RDFRule
makeRdfSimpleEntailmentRule ScopedName
name = RDFRule
newrule
where
newrule :: RDFRule
newrule = Rule :: forall ex.
ScopedName
-> ([ex] -> [ex])
-> (ex -> [[ex]])
-> ([ex] -> ex -> Bool)
-> Rule ex
Rule
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [RDFGraph] -> [RDFGraph]
fwdApply = [RDFGraph] -> [RDFGraph] -> [RDFGraph]
forall a b. a -> b -> a
const []
, bwdApply :: RDFGraph -> [[RDFGraph]]
bwdApply = [[RDFGraph]] -> RDFGraph -> [[RDFGraph]]
forall a b. a -> b -> a
const []
, checkInference :: [RDFGraph] -> RDFGraph -> Bool
checkInference = [RDFGraph] -> RDFGraph -> Bool
rdfSimpleEntailCheckInference
}
rdfSimpleEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSimpleEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSimpleEntailCheckInference [RDFGraph]
ante RDFGraph
cons =
let agr :: RDFGraph
agr = if [RDFGraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RDFGraph]
ante then RDFGraph
forall a. Monoid a => a
mempty else (RDFGraph -> RDFGraph -> RDFGraph) -> [RDFGraph] -> RDFGraph
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 RDFGraph -> RDFGraph -> RDFGraph
forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [RDFGraph]
ante
in Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [VarBinding RDFLabel RDFLabel] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([VarBinding RDFLabel RDFLabel] -> Bool)
-> [VarBinding RDFLabel RDFLabel] -> Bool
forall a b. (a -> b) -> a -> b
$ RDFGraph -> RDFGraph -> [VarBinding RDFLabel RDFLabel]
rdfQueryInstance RDFGraph
cons RDFGraph
agr