Portability | OverloadedStrings |
---|---|
Stability | experimental |
Maintainer | Douglas Burke |
Safe Haskell | None |
This module defines some datatypes and functions that are used to define rules and rulesets over RDF graphs.
For the routines that accept a graph in N3 format, the following
namespaces are pre-defined for use by the graph:
rdf:
and rdfs:
.
- type RDFFormula = Formula RDFGraph
- type RDFRule = Rule RDFGraph
- type RDFRuleMap = RuleMap RDFGraph
- type RDFClosure = GraphClosure RDFLabel
- type RDFRuleset = Ruleset RDFGraph
- type RDFRulesetMap = RulesetMap RDFGraph
- nullRDFFormula :: Formula RDFGraph
- data GraphClosure lb = GraphClosure {
- nameGraphRule :: ScopedName
- ruleAnt :: ArcSet lb
- ruleCon :: ArcSet lb
- ruleModify :: VarBindingModify lb lb
- makeGraphClosureRule :: GraphClosure RDFLabel -> Rule RDFGraph
- makeRDFGraphFromN3Builder :: Builder -> RDFGraph
- makeRDFFormula :: Namespace -> LName -> Builder -> RDFFormula
- makeRDFClosureRule :: ScopedName -> [RDFGraph] -> RDFGraph -> RDFVarBindingModify -> RDFRule
- makeN3ClosureRule :: Namespace -> LName -> Builder -> Builder -> RDFVarBindingModify -> RDFRule
- makeN3ClosureSimpleRule :: Namespace -> LName -> Builder -> Builder -> RDFRule
- makeN3ClosureModifyRule :: Namespace -> LName -> Builder -> Builder -> RDFVarBindingModify -> RDFVarBindingModify -> RDFRule
- makeN3ClosureAllocatorRule :: Namespace -> LName -> Builder -> Builder -> RDFVarBindingModify -> ([RDFLabel] -> RDFVarBindingModify) -> RDFRule
- makeNodeAllocTo :: RDFLabel -> RDFLabel -> [RDFLabel] -> RDFVarBindingModify
- graphClosureFwdApply :: GraphClosure RDFLabel -> [RDFGraph] -> [RDFGraph]
- graphClosureBwdApply :: GraphClosure RDFLabel -> RDFGraph -> [[RDFGraph]]
Data types for RDF Ruleset
type RDFFormula = Formula RDFGraphSource
A named formula expressed as a RDF Graph.
type RDFRuleMap = RuleMap RDFGraphSource
A map for RDFRule
rules.
type RDFClosure = GraphClosure RDFLabelSource
A GraphClosure
for RDF statements.
type RDFRuleset = Ruleset RDFGraphSource
A Ruleset
for RDF.
type RDFRulesetMap = RulesetMap RDFGraphSource
A map for RDFRuleset
.
nullRDFFormula :: Formula RDFGraphSource
The null RDF formula.
data GraphClosure lb Source
Datatype for constructing a graph closure rule
GraphClosure | |
|
Label lb => Eq (GraphClosure lb) | Equality is based on the closure rule, anrecedents and consequents. |
Label lb => Show (GraphClosure lb) |
makeGraphClosureRule :: GraphClosure RDFLabel -> Rule RDFGraphSource
Define a value of type Rule based on an RDFClosure value.
makeRDFGraphFromN3Builder :: Builder -> RDFGraphSource
Helper function to parse a string containing Notation3 and return the corresponding RDFGraph value.
:: Namespace | namespace to which the formula is allocated |
-> LName | local name for the formula in the namespace |
-> Builder | graph in Notation 3 format |
-> RDFFormula |
Create an RDF formula.
:: ScopedName | scoped name for the new rule |
-> [RDFGraph] | RDFGraphs that are the entecedent of the rule. (Note: bnodes and variable names are assumed to be shared by all the entecedent graphs supplied. is this right?) |
-> RDFGraph | the consequent graph |
-> RDFVarBindingModify | is a variable binding modifier value that may impose additional conditions on the variable bindings that can be used for this inference rule, or which may cause new values to be allocated for unbound variables. These modifiers allow for certain inference patterns that are not captured by simple closure rules, such as the allocation of bnodes corresponding to literals, and are an extension point for incorporating datatypes into an inference process. If no additional constraints or variable bindings are
to be applied, use value |
-> RDFRule |
Constructs an RDF graph closure rule. That is, a rule that given some set of antecedent statements returns new statements that may be added to the graph.
Create rules using Notation3 statements
:: Namespace | namespace to which the rule is allocated |
-> LName | local name for the rule in the namespace |
-> Builder | the Notation3 representation of the antecedent graph. (Note: multiple antecedents can be handled by combining multiple graphs.) |
-> Builder | the Notation3 representation of the consequent graph. |
-> RDFVarBindingModify | a variable binding modifier value that may impose additional conditions on the variable bindings that can be used for this inference rule, or which may cause new values to be allocated for unbound variables. These modifiers allow for certain inference patterns that are not captured by simple closure rules, such as the allocation of bnodes corresponding to literals, and are an extension point for incorporating datatypes into an inference process. If no additional constraints or variable bindings are
to be applied, use a value of |
-> RDFRule |
Constructs an RDF graph closure rule. That is, a rule that given some set of antecedent statements returns new statements that may be added to the graph. This is the basis for implementation of most of the inference rules given in the RDF formal semantics document.
:: Namespace | namespace to which the rule is allocated |
-> LName | local name for the rule in the namepace |
-> Builder | the Notation3 representation of the antecedent graph. (Note: multiple antecedents can be handled by combining multiple graphs.) |
-> Builder | the Notation3 representation of the consequent graph. |
-> RDFRule |
Construct a simple RDF graph closure rule without additional node allocations or variable binding constraints.
:: Namespace | namespace to which the rule is allocated |
-> LName | local name for the rule in the given namespace |
-> Builder | the Notation3 representation of the antecedent graph. (Note: multiple antecedents can be handled by combining multiple graphs.) |
-> Builder | the Notation3 representation of the consequent graph. |
-> RDFVarBindingModify | a variable binding modifier value that may impose
additional conditions on the variable bindings that
can be used for this inference rule ( These modifiers allow for certain inference patterns that are not captured by simple closure rules, such as deductions that pertain only to certain kinds of nodes in a graph. |
-> RDFVarBindingModify | a variable binding modifier that is applied to the
variable bindings obtained, typically to create some
additional variable bindings. This is applied before
the preceeding filter rule ( |
-> RDFRule |
Constructs an RDF graph closure rule that incorporates a variable binding filter and a variable binding modifier.
makeN3ClosureAllocatorRuleSource
:: Namespace | namespace to which the rule is allocated |
-> LName | local name for the rule in the given namespace |
-> Builder | the Notation3 representation of the antecedent graph. (Note: multiple antecedents can be handled by combining multiple graphs.) |
-> Builder | the Notation3 representation of the consequent graph. |
-> RDFVarBindingModify | variable binding modifier value that may impose
additional conditions on the variable bindings that
can be used for this inference rule ( |
-> ([RDFLabel] -> RDFVarBindingModify) | function applied to a list of nodes to yield a variable binding modifier value. The supplied parameter is applied to a list of all of
the variable nodes (including all blank nodes) in the
antecedent graph, and then composed with the |
-> RDFRule |
Construct an RDF graph closure rule with a bnode allocator.
This function is rather like makeN3ClosureModifyRule
, except that
the variable binding modifier is a function from the variables in
the variables and bnodes contained in the antecedent graph.
:: RDFLabel | variable node to which a new blank node is bound |
-> RDFLabel | variable which is bound in each query to a graph node to which new blank nodes are allocated. |
-> [RDFLabel] | |
-> RDFVarBindingModify |
This function defines a variable binding modifier that allocates a new blank node for each value bound to a query variable, and binds it to another variable in each query binding.
This provides a single binding for query variables that would otherwise be unbound by a query. For example, consider the inference pattern:
?a hasUncle ?c => ?a hasFather ?b . ?b hasBrother ?c .
For a given ?a
and ?c
, there is insufficient information
here to instantiate a value for variable ?b
. Using this
function as part of a graph instance closure rule allows
forward chaining to allocate a single bnode for each
occurrence of ?a
, so that given:
Jimmy hasUncle Fred . Jimmy hasUncle Bob .
leads to exactly one bnode inference of:
Jimmy hasFather _:f .
giving:
Jimmy hasFather _:f . _:f hasBrother Fred . _:f hasBrother Bob .
rather than:
Jimmy hasFather _:f1 . _:f1 hasBrother Fred . Jimmy hasFather _:f2 . _:f2 hasBrother Bob .
This form of constrained allocation of bnodes is also required for some of the inference patterns described by the RDF formal semantics, particularly those where bnodes are substituted for URIs or literals.
Debugging
graphClosureFwdApply :: GraphClosure RDFLabel -> [RDFGraph] -> [RDFGraph]Source
Forward chaining function based on RDF graph closure description
Note: antecedents here are presumed to share bnodes.
graphClosureBwdApply :: GraphClosure RDFLabel -> RDFGraph -> [[RDFGraph]]Source
Backward chaining function based on RDF graph closure description