swish-0.6.0.1: A semantic web toolkit.

PortabilityExistentialQuantification, MultiParamTypeClasses, OverloadedStrings
Stabilityexperimental
MaintainerDouglas Burke

Swish.RDF.Datatype

Description

This module defines the structures used by Swish to represent and manipulate datatypes. It is designed as a basis for handling datatyped RDF literals, but the functions in this module are more generic.

Synopsis

Documentation

data Datatype ex lb vn Source

Datatype wraps a DatatypeVal value, hiding the value type that is used only in implementations of the datatype. Users see just the datatype name and associated ruleset.

Constructors

forall vt . Datatype (DatatypeVal ex vt lb vn) 

Instances

typeName :: Datatype ex lb vn -> ScopedNameSource

Get type name from Datatype value

typeRules :: Datatype ex lb vn -> Ruleset exSource

Get static rules from Datatype value

typeMkRules :: Datatype ex lb vn -> ex -> [Rule ex]Source

Make rules for Datatype value based on supplied expression

typeMkModifiers :: Datatype ex lb vn -> [OpenVarBindingModify lb vn]Source

Make variable binding modifiers based on values supplied

typeMkCanonicalForm :: Datatype ex lb vn -> Text -> Maybe TextSource

Get the canonical form of a datatype value.

getTypeAxiom :: ScopedName -> Datatype ex lb vn -> Maybe (Formula ex)Source

Get the named axiom from a Datatype value.

getTypeRule :: ScopedName -> Datatype ex lb vn -> Maybe (Rule ex)Source

Get the named rule from a Datatype value.

data DatatypeVal ex vt lb vn Source

DatatypeVal is a structure that defines a number of functions and values that characterize the behaviour of a datatype.

A datatype is specified with respect to (polymophic in) a given type of (syntactic) expression with which it may be used, and a value type (whose existence is hidden as an existential type within DatatypeMap).

(I tried hiding the value type with an internal existential declaration, but that wouldn't wash. Hence this two-part structure with Datatype in which the internal detail of the value type is hidden from users of the Datatype class.)

The datatype characteristic functions have two goals:

  1. to support the general datatype entailment rules defined by the RDF semantics specification, and
  2. to define additional datatype-specific inference patterns by means of which provide additional base functionality to applications based on RDF inference.

Datatype-specific inferences are provided using the DatatypeRel structure for a datatype, which allows a number of named relations to be defined on datatype values, and provides mechanisms to calculate missing values in a partially-specified member of a relation.

Note that rules and variable binding modifiers that deal with combined values of more than one datatype may be defined separately. Definitions in this module are generally applicable only when using a single datatype.

An alternative model for datatype value calculations is inspired by that introduced by CWM for arithmetic operations, e.g.

     (1 2 3) math:sum ?x => ?x rdf:value 6

(where the bare integer n here is shorthand for "n"^^xsd:integer).

Datatype-specific inference patterns are provided in two ways:

  • by variable binding modifiers that can be combined with the query results during forward- for backward-chaining of inference rules, and
  • by the definition of inference rulesets that involve datatype values.

I believe the first method to be more flexible than the second, in that it more readily supports forward and backward chaining, but can be used only through the definition of new rules.

Type parameters:

ex
is the type of expression with which the datatype may be used.
vt
is the internal value type with which the labels are associated.
lb
is the type of label that may be used as a variable in an expression or rule.
vn
is the type of node that may be used to carry a value in an expression or rule.

Constructors

DatatypeVal 

Fields

tvalName :: ScopedName

Identifies the datatype, and also its value space class.

tvalRules :: Ruleset ex

A set of named expressions and rules that are valid in in any theory that recognizes the current datatype.

tvalMkRules :: ex -> [Rule ex]

A function that accepts an expression and devives some datatype-dependent rules from it. This is provided as a hook for creating datatyped class restriction rules.

tvalMkMods :: [OpenVarBindingModify lb vn]

Constructs a list of open variable binding modifiers based on tvalMod, but hiding the actual value type.

tvalMap :: DatatypeMap vt

Lexical to value mapping, where vt is a datatype used within a Haskell program to represent and manipulate values in the datatype's value space

tvalRel :: [DatatypeRel vt]

A set of named relations on datatype values. Each relation accepts a list of Maybe vt, and computes any unspecified values that are in the relation with values supplied.

tvalMod :: [DatatypeMod vt lb vn]

A list of named values that are used to construct variable binding modifiers, which in turn may be used by a rule definition.

TODO: In due course, this value may be calculated automatically from the supplied value for tvalRel.

getDTMod :: ScopedName -> DatatypeVal ex vt lb vn -> Maybe (DatatypeMod vt lb vn)Source

tvalMkCanonicalForm :: DatatypeVal ex vt lb vn -> Text -> Maybe TextSource

Get the canonical form of a datatype value, or Nothing.

data DatatypeMap vt Source

DatatypeMap consists of methods that perform lexical-to-value and value-to-canonical-lexical mappings for a datatype.

The datatype mappings apply to string lexical forms which are stored as Data.Text.

Constructors

DatatypeMap 

Fields

mapL2V :: Text -> Maybe vt

Function to map a lexical string to the datatype value. This effectively defines the lexical space of the datatype to be all strings for which yield a value other than Nothing.

mapV2L :: vt -> Maybe Text

Function to map a value to its canonical lexical form, if it has such.

data DatatypeRel vt Source

Datatype for a named relation on values of a datatype.

Constructors

DatatypeRel 

type DatatypeRelFn vt = [Maybe vt] -> Maybe [[vt]]Source

Type for a datatype relation inference function.

A datatype relation defines tuples of values that satisfy some relation. A datatype relation inference function calculates values that complete a relation with values supplied.

The function accepts a list of Maybe vt, where vt is the datatype value type. It returns one of:

  • Just a list of lists, where each inner list returned is a complete set of values, including the values supplied, that are in the relation.
  • Just an empty list is returned if the supplied values are insufficient to compute any complete sets of values in the relation.
  • Nothing if the supplied values are not consistent with the relation.

type DatatypeRelPr vt = [vt] -> BoolSource

Type for datatype relation predicate: accepts a list of values and determines whether or not they satisfy the relation.

altArgsSource

Arguments

:: Eq vt 
=> DatatypeRelPr vt 
-> [(vt -> Bool, [b])]

a list of argument value predicates and function descriptors. The predicate indicates any additional constraints on argument values (e.g. the result of abs must be positive). Use (const True) for the predicate associated with unconstrained relation arguments. For each argument, a list of function descriptors is supplied corresponding to alternative values (e.g. a square relation would offer two alternative values for the root.)

-> ((vt -> Bool) -> b -> [Maybe vt] -> Maybe [vt])

a function that takes an argument value predicate, a function descriptor and applies it to a supplied argument list to return: Just a calculated list of one or more possible argument values, Just [] indicating insufficient information provided, or Nothing indicating inconsistent information provided. May be one of unaryFnApp, binaryFnApp, listFnApp or some other caller-supplied value.

-> DatatypeRelFn vt

The return value can be used as the dtRelFunc component of a DatatypeRel value.

Given a list of argument values and a list of functions for calculating new values from supplied values, return a list of argument values, or Nothing if the supplied values are inconsistent with the calculations specified.

Each list of values returned corresponds to a set of values that satisfy the relation, consistent with the values supplied.

Functions are described as tuple consisting of:

(a) a predicate that the argument is required to satisfy

(b) a function to apply,

(c) a function to apply function (b) to a list of arguments

(d) argument list index values to which the function is applied.

Each supplied argument is of the form Maybe a, where the argument has value type a. Nothing indicates arguments of unknown value.

The basic idea is that, for each argument position in the relation, a function may be supplied to calculate that argument's possible values from some combination of the other arguments. The results calculated in this way are compared with the original arguments provided: if the values conflict then the relation is presumed to be unsatisfiable with the supplied values, and Nothing is returned; if there are any calculated values for arguments supplied without any values, then tbe calculated values are used. If there are any arguments for which no values are supplied or calculated, then the relation is presumed to be underdetermined, and Just [] is returned.

type UnaryFnDescr a = (a -> a, Int)Source

altArgs support for unary functions: function descriptor type

type UnaryFnTable a = [(a -> Bool, [UnaryFnDescr a])]Source

altArgs support for unary functions: function descriptor table type

type UnaryFnApply a = (a -> Bool) -> UnaryFnDescr a -> [Maybe a] -> Maybe [a]Source

altArgs support for unary functions: function applicator type

unaryFnApp :: UnaryFnApply aSource

altArgs support for unary functions: function applicator

type BinaryFnDescr a = (a -> a -> a, Int, Int)Source

altArgs support for binary functions: function descriptor type

type BinaryFnTable a = [(a -> Bool, [BinaryFnDescr a])]Source

altArgs support for binary functions: function descriptor table type

type BinaryFnApply a = (a -> Bool) -> BinaryFnDescr a -> [Maybe a] -> Maybe [a]Source

altArgs support for binary functions: function applicator type

binaryFnApp :: BinaryFnApply aSource

altArgs support for binary functions: function applicator

type BinMaybeFnDescr a = (a -> a -> Maybe [a], Int, Int)Source

altArgs support for binary function with provision for indicating inconsistent supplied values: function descriptor type

type BinMaybeFnTable a = [(a -> Bool, [BinMaybeFnDescr a])]Source

altArgs support for binary function with provision for indicating inconsistent supplied values: function descriptor table type

type BinMaybeFnApply a = (a -> Bool) -> BinMaybeFnDescr a -> [Maybe a] -> Maybe [a]Source

altArgs support for binary function with provision for indicating inconsistent supplied values: function applicator type

binMaybeFnApp :: BinMaybeFnApply aSource

altArgs support for binary function with provision for indicating inconsistent supplied values: function applicator

type ListFnDescr a = (a -> a -> a, a, a -> a -> a, Int)Source

altArgs support for list functions (e.g. sum over list of args), where first element of list is a fold over the rest of the list, and remaining elements of list can be calculated in terms of the result of the fold and the remaining elements

List function descriptor is

(a) list-fold function, f (e.g. (+)

(b) list-fold identity, z (e.g. 0)

(c) list-fold-function inverse, g (e.g. (-))

(d) index of element to evaluate

such that:

    (a `f` z) == (z `f` a) == a
    (a `g` c) == b <=> a == b `f` c
    (a `g` z) == a
    (a `g` a) == z

and the result of the folded function does not depend on the order that the list elements are processed.

NOTE: the list of ListFnDescr values supplied to altArgs must be at least as long as the argument list. In many cases, Haskell lazy evaluation can be used to supply an arbitrarily long list. See test cases in spike-altargs.hs for an example.

Function descriptor type

type ListFnTable a = [(a -> Bool, [ListFnDescr a])]Source

Function table type

type ListFnApply a = (a -> Bool) -> ListFnDescr a -> [Maybe a] -> Maybe [a]Source

altArgs support for list functions: function applicator type

listFnApp :: ListFnApply aSource

altArgs support for list functions: function applicator

data DatatypeMod vt lb vn Source

Wrapper for data type variable binding modifier included in a datatype value.

Constructors

DatatypeMod 

Fields

dmName :: ScopedName
 
dmModf :: [ModifierFn vt]
 
dmAppf :: ApplyModifier lb vn
 

Instances

type ModifierFn vn = [vn] -> [vn]Source

Datatype value modifier functions type

Each function accepts a list of values and returns a list of values. The exact significance of the different values supplied and returned depends on the variable binding pattern used (cf. ApplyModifier), but in all cases an empty list returned means that the corresponding inputs are not consistent with the function and cannot be used.

type ApplyModifier lb vn = ScopedName -> [ModifierFn vn] -> OpenVarBindingModify lb vnSource

Type of function used to apply a data value modifier to specified variables in a supplied variable binding. It also accepts the name of the datatype modifier and carries it into the resulting variable binding modifier.

(Note that vn is not necessarily the same as vt, the datatype value type: the modifier functions may be lifted or otherwise adapted to operate on some other type from which the raw data values are extracted.)

nullDatatypeMod :: DatatypeMod vt lb vnSource

Null datatype value modifier

makeVmod11inv :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a 1->1 function and inverse, such as negate.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x and y are in the appropriate relationship.
  2. is [y] -> [x], used to perform the calculation in a forward direction.
  3. is [x] -> [y], used to perform the calculation in a backward direction. This may be the same as (2) (e.g. for negation) or may be different (e.g. increment).
lbs
is a list of specific label values for which a variable binding modifier will be generated. (The intent is that a variable-free value can be generated as a Curried function, and instantiated for particular variables as required.)

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

makeVmod11 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a non-invertable 1->1 injection, such as absolute value.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x and y are in the appropriate relationship.
  2. is [x] -> [y], used to perform the calculation.
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

makeVmod21inv :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a 2->1 invertable function, such as addition or subtraction.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y,z] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x, y and z are in the appropriate relationship.
  2. is [y,z] -> [x], used to perform the calculation in a forward direction.
  3. is [x,z] -> [y], used to run the calculation backwards to determine the first input argument
  4. is [x,y] -> [z], used to run the calculation backwards to determine the second input argument
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

makeVmod21 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a 2->1 non-invertable function, such as logical AND or OR.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y,z] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x, y and z are in the appropriate relationship.
  2. is [y,z] -> [x], used to perform the calculation in a forward direction.
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

makeVmod20 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a simple comparson of two values.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x and y are in the appropriate relationship.
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

makeVmod22 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a 2->2 non-invertable function, such as quotient/remainder

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [w,x,y,z] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if w, x, y and z are in the appropriate relationship.
  2. is [y,z] -> [w,x], used to perform the calculation given two input values.
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

NOTE: this might be generalized to allow one of w or x to be specified, and return null if it doesn't match the calculated value.

makeVmodN1 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vnSource

ApplyModifier function for use with DatatypeMod in cases when the value mapping is a N->1 function, such as Sigma (sum) of a vector.

nam
is the name from the DatatypeMod value that is carried into the resulting variable binding modifier.
fns
are functions used to implement details of the variable binding modifier:
  1. is [x,y...] -> [?], used as a filter (i.e. not creating any new variable bindings), returning a non-empty list if x and y... are in the appropriate relationship.
  2. is [y...] -> [x], used to perform the calculation.
lbs
is a list of specific label values for which a variable binding modifier will be generated.

Note: an irrefutable pattern match for lbs is used so that a name for the VarBindingModify value can be extracted using an undefined label value.

data DatatypeSub ex lb vn supvt subvt Source

Describe a subtype/supertype relationship between a pair of datatypes.

Originally, I had this as a supertype field of the DatatypeVal structure, but that suffered from some problems:

  • supertypes may be introduced retrospectively,
  • the relationship expressed with respect to a single datatype cannot indicate how to do injections/restrictions between the underlying value types.
ex
is the type of expression with which the datatype may be used.
lb
is the type of the variable labels used.
vn
is the type of value node used to contain a datatyped value
supvt
is the internal value type of the super-datatype
subvt
is the internal value type of the sub-datatype

Constructors

DatatypeSub 

Fields

trelSup :: DatatypeVal ex supvt lb vn

Datatype that is a supertype of trelSub, having value space supvt.

trelSub :: DatatypeVal ex subvt lb vn

Datatype that is a subtype of trelSup, having value space supvt.

trelToSup :: subvt -> supvt

Function that maps subtype value to corresponding supertype value.

trelToSub :: supvt -> Maybe subvt

Function that maps supertype value to corresponding subtype value, if there is such a value.