{-# 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 = forall a. Set a -> Bool
S.null forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
{ 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
{ 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
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [NSGraph RDFLabel] -> [NSGraph RDFLabel]
fwdApply = [RDFLabel] -> [NSGraph RDFLabel] -> [NSGraph RDFLabel]
rdfInstanceEntailFwdApply [RDFLabel]
vocab
, bwdApply :: NSGraph RDFLabel -> [[NSGraph RDFLabel]]
bwdApply = [RDFLabel] -> NSGraph RDFLabel -> [[NSGraph RDFLabel]]
rdfInstanceEntailBwdApply [RDFLabel]
vocab
, checkInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
checkInference = [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfInstanceEntailCheckInference
}
rdfInstanceEntailFwdApply :: [RDFLabel] -> [RDFGraph] -> [RDFGraph]
rdfInstanceEntailFwdApply :: [RDFLabel] -> [NSGraph RDFLabel] -> [NSGraph RDFLabel]
rdfInstanceEntailFwdApply [RDFLabel]
vocab [NSGraph RDFLabel]
ante =
let
mergeGraph :: NSGraph RDFLabel
mergeGraph = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NSGraph RDFLabel]
ante then forall a. Monoid a => a
mempty
else forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [NSGraph RDFLabel]
ante
nonvarNodes :: [RDFLabel]
nonvarNodes = [RDFLabel]
vocab
varNodes :: [RDFLabel]
varNodes = forall a. Set a -> [a]
S.toList forall a b. (a -> b) -> a -> b
$ forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels forall lb. Label lb => lb -> Bool
labelIsVar NSGraph RDFLabel
mergeGraph
mapList :: [(RDFLabel, RDFLabel)]
mapList = forall lb. Label lb => [lb] -> [lb] -> [(lb, lb)]
remapLabelList [RDFLabel]
nonvarNodes [RDFLabel]
varNodes
mapSubLists :: [[(RDFLabel, RDFLabel)]]
mapSubLists = (forall a. [a] -> [a]
tail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [[a]]
subsequences) [(RDFLabel, RDFLabel)]
mapList
mapGr :: [(k, k)] -> NSGraph k -> NSGraph k
mapGr [(k, k)]
ls = forall lb. Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph
(\k
l -> forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault k
l k
l
(forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(k, k)]
ls))
in
forall a b. [a -> b] -> a -> [b]
flist (forall a b. (a -> b) -> [a] -> [b]
map forall {k}. Ord k => [(k, k)] -> NSGraph k -> NSGraph k
mapGr [[(RDFLabel, RDFLabel)]]
mapSubLists) NSGraph RDFLabel
mergeGraph
rdfInstanceEntailBwdApply :: [RDFLabel] -> RDFGraph -> [[RDFGraph]]
rdfInstanceEntailBwdApply :: [RDFLabel] -> NSGraph RDFLabel -> [[NSGraph RDFLabel]]
rdfInstanceEntailBwdApply [RDFLabel]
vocab NSGraph RDFLabel
cons =
let
varNodes :: [RDFLabel]
varNodes = forall a. Set a -> [a]
S.toList forall a b. (a -> b) -> a -> b
$ forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels forall lb. Label lb => lb -> Bool
labelIsVar NSGraph RDFLabel
cons
varBindings :: [VarBinding RDFLabel RDFLabel]
varBindings = forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (Ord a, Ord b) => [(a, b)] -> VarBinding a b
makeVarBinding forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [RDFLabel]
varNodes) [[RDFLabel]]
vocSequences
vocSequences :: [[RDFLabel]]
vocSequences = forall a. Int -> [a] -> [[a]]
powerSequencesLen (forall (t :: * -> *) a. Foldable t => t a -> Int
length [RDFLabel]
varNodes) [RDFLabel]
vocab
in
[ [VarBinding RDFLabel RDFLabel]
-> NSGraph RDFLabel -> [NSGraph RDFLabel]
rdfQuerySubs [VarBinding RDFLabel RDFLabel
v] NSGraph RDFLabel
cons | VarBinding RDFLabel RDFLabel
v <- [VarBinding RDFLabel RDFLabel]
varBindings ]
rdfInstanceEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfInstanceEntailCheckInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfInstanceEntailCheckInference [NSGraph RDFLabel]
ante NSGraph RDFLabel
cons =
let
mante :: NSGraph RDFLabel
mante = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NSGraph RDFLabel]
ante then forall a. Monoid a => a
mempty
else forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [NSGraph RDFLabel]
ante
qvars :: [VarBinding RDFLabel RDFLabel]
qvars = NSGraph RDFLabel
-> NSGraph RDFLabel -> [VarBinding RDFLabel RDFLabel]
rdfQueryInstance NSGraph RDFLabel
cons NSGraph RDFLabel
mante
bsubs :: [NSGraph RDFLabel]
bsubs = [VarBinding RDFLabel RDFLabel]
-> NSGraph RDFLabel -> [NSGraph RDFLabel]
rdfQuerySubs [VarBinding RDFLabel RDFLabel]
qvars NSGraph RDFLabel
cons
in
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem NSGraph RDFLabel
mante [NSGraph RDFLabel]
bsubs
powerSeqBylen :: [a] -> [[a]] -> [[[a]]]
powerSeqBylen :: forall a. [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs [[a]]
ps = [[a]]
ps forall a. a -> [a] -> [a]
: forall a. [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs (forall a. [a] -> [[a]] -> [[a]]
powerSeqNext [a]
rs [[a]]
ps)
powerSeqNext :: [a] -> [[a]] -> [[a]]
powerSeqNext :: forall a. [a] -> [[a]] -> [[a]]
powerSeqNext [a]
rs [[a]]
rss = [ a
hforall a. a -> [a] -> [a]
:[a]
t | [a]
t <- [[a]]
rss, a
h <- [a]
rs ]
powerSequencesLen :: Int -> [a] -> [[a]]
powerSequencesLen :: forall a. Int -> [a] -> [[a]]
powerSequencesLen Int
len [a]
rs = forall a. [a] -> [[a]] -> [[[a]]]
powerSeqBylen [a]
rs [[]] forall a. [a] -> Int -> a
!! Int
len
makeRdfSubgraphEntailmentRule :: ScopedName -> RDFRule
makeRdfSubgraphEntailmentRule :: ScopedName -> RDFRule
makeRdfSubgraphEntailmentRule ScopedName
name = RDFRule
newrule
where
newrule :: RDFRule
newrule = Rule
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [NSGraph RDFLabel] -> [NSGraph RDFLabel]
fwdApply = [NSGraph RDFLabel] -> [NSGraph RDFLabel]
rdfSubgraphEntailFwdApply
, bwdApply :: NSGraph RDFLabel -> [[NSGraph RDFLabel]]
bwdApply = forall a b. a -> b -> a
const []
, checkInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
checkInference = [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfSubgraphEntailCheckInference
}
rdfSubgraphEntailFwdApply :: [RDFGraph] -> [RDFGraph]
rdfSubgraphEntailFwdApply :: [NSGraph RDFLabel] -> [NSGraph RDFLabel]
rdfSubgraphEntailFwdApply [NSGraph RDFLabel]
ante =
let
mergeGraph :: NSGraph RDFLabel
mergeGraph = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NSGraph RDFLabel]
ante then forall a. Monoid a => a
mempty
else forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [NSGraph RDFLabel]
ante
in
forall a b. (a -> b) -> [a] -> [b]
map (forall (lg :: * -> *) lb.
LDGraph lg lb =>
lg lb -> ArcSet lb -> lg lb
setArcs NSGraph RDFLabel
mergeGraph forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Set a
S.fromList) (forall a. [a] -> [a]
init forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [[a]]
subsequences forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
S.toList forall a b. (a -> b) -> a -> b
$ forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph RDFLabel
mergeGraph)
rdfSubgraphEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSubgraphEntailCheckInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfSubgraphEntailCheckInference [NSGraph RDFLabel]
ante NSGraph RDFLabel
cons =
let
fullGraph :: NSGraph RDFLabel
fullGraph = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NSGraph RDFLabel]
ante then forall a. Monoid a => a
mempty
else forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [NSGraph RDFLabel]
ante
in
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph RDFLabel
cons forall a. Ord a => Set a -> Set a -> Bool
`S.isSubsetOf` forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph RDFLabel
fullGraph
makeRdfSimpleEntailmentRule :: ScopedName -> RDFRule
makeRdfSimpleEntailmentRule :: ScopedName -> RDFRule
makeRdfSimpleEntailmentRule ScopedName
name = RDFRule
newrule
where
newrule :: RDFRule
newrule = Rule
{ ruleName :: ScopedName
ruleName = ScopedName
name
, fwdApply :: [NSGraph RDFLabel] -> [NSGraph RDFLabel]
fwdApply = forall a b. a -> b -> a
const []
, bwdApply :: NSGraph RDFLabel -> [[NSGraph RDFLabel]]
bwdApply = forall a b. a -> b -> a
const []
, checkInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
checkInference = [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfSimpleEntailCheckInference
}
rdfSimpleEntailCheckInference :: [RDFGraph] -> RDFGraph -> Bool
rdfSimpleEntailCheckInference :: [NSGraph RDFLabel] -> NSGraph RDFLabel -> Bool
rdfSimpleEntailCheckInference [NSGraph RDFLabel]
ante NSGraph RDFLabel
cons =
let agr :: NSGraph RDFLabel
agr = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NSGraph RDFLabel]
ante then forall a. Monoid a => a
mempty else forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [NSGraph RDFLabel]
ante
in Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ NSGraph RDFLabel
-> NSGraph RDFLabel -> [VarBinding RDFLabel RDFLabel]
rdfQueryInstance NSGraph RDFLabel
cons NSGraph RDFLabel
agr