Copyright | (c) 2003 Graham Klyne 2009 Vasili I Galchin 2011 2012 2018 2019 2022 Douglas Burke |
---|---|
License | GPL V2 |
Maintainer | Douglas Burke |
Stability | experimental |
Portability | ExistentialQuantification, OverloadedStrings |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines the structures used 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
- data Datatype ex lb vn = forall vt. Datatype (DatatypeVal ex vt lb vn)
- typeName :: Datatype ex lb vn -> ScopedName
- typeRules :: Datatype ex lb vn -> Ruleset ex
- typeMkRules :: Datatype ex lb vn -> ex -> [Rule ex]
- typeMkModifiers :: Datatype ex lb vn -> [OpenVarBindingModify lb vn]
- typeMkCanonicalForm :: Datatype ex lb vn -> Text -> Maybe Text
- getTypeAxiom :: ScopedName -> Datatype ex lb vn -> Maybe (Formula ex)
- getTypeRule :: ScopedName -> Datatype ex lb vn -> Maybe (Rule ex)
- data DatatypeVal ex vt lb vn = DatatypeVal {
- tvalName :: ScopedName
- tvalRules :: Ruleset ex
- tvalMkRules :: ex -> [Rule ex]
- tvalMkMods :: [OpenVarBindingModify lb vn]
- tvalMap :: DatatypeMap vt
- tvalRel :: [DatatypeRel vt]
- tvalMod :: [DatatypeMod vt lb vn]
- getDTMod :: ScopedName -> DatatypeVal ex vt lb vn -> Maybe (DatatypeMod vt lb vn)
- getDTRel :: ScopedName -> DatatypeVal ex vt lb vn -> Maybe (DatatypeRel vt)
- tvalMkCanonicalForm :: DatatypeVal ex vt lb vn -> Text -> Maybe Text
- data DatatypeMap vt = DatatypeMap {}
- data DatatypeRel vt = DatatypeRel {
- dtRelName :: ScopedName
- dtRelFunc :: DatatypeRelFn vt
- type DatatypeRelFn vt = [Maybe vt] -> Maybe [[vt]]
- type DatatypeRelPr vt = [vt] -> Bool
- altArgs :: Eq vt => DatatypeRelPr vt -> [(vt -> Bool, [b])] -> ((vt -> Bool) -> b -> [Maybe vt] -> Maybe [vt]) -> DatatypeRelFn vt
- type UnaryFnDescr a = (a -> a, Int)
- type UnaryFnTable a = [(a -> Bool, [UnaryFnDescr a])]
- type UnaryFnApply a = (a -> Bool) -> UnaryFnDescr a -> [Maybe a] -> Maybe [a]
- unaryFnApp :: UnaryFnApply a
- type BinaryFnDescr a = (a -> a -> a, Int, Int)
- type BinaryFnTable a = [(a -> Bool, [BinaryFnDescr a])]
- type BinaryFnApply a = (a -> Bool) -> BinaryFnDescr a -> [Maybe a] -> Maybe [a]
- binaryFnApp :: BinaryFnApply a
- type BinMaybeFnDescr a = (a -> a -> Maybe [a], Int, Int)
- type BinMaybeFnTable a = [(a -> Bool, [BinMaybeFnDescr a])]
- type BinMaybeFnApply a = (a -> Bool) -> BinMaybeFnDescr a -> [Maybe a] -> Maybe [a]
- binMaybeFnApp :: BinMaybeFnApply a
- type ListFnDescr a = (a -> a -> a, a, a -> a -> a, Int)
- type ListFnTable a = [(a -> Bool, [ListFnDescr a])]
- type ListFnApply a = (a -> Bool) -> ListFnDescr a -> [Maybe a] -> Maybe [a]
- listFnApp :: ListFnApply a
- data DatatypeMod vt lb vn = DatatypeMod {
- dmName :: ScopedName
- dmModf :: [ModifierFn vt]
- dmAppf :: ApplyModifier lb vn
- type ModifierFn vn = [vn] -> [vn]
- type ApplyModifier lb vn = ScopedName -> [ModifierFn vn] -> OpenVarBindingModify lb vn
- nullDatatypeMod :: DatatypeMod vt lb vn
- makeVmod11inv :: (Ord lb, Ord vn) => ApplyModifier lb vn
- makeVmod11 :: (Ord lb, Ord vn) => ApplyModifier lb vn
- makeVmod21inv :: (Ord lb, Ord vn) => ApplyModifier lb vn
- makeVmod21 :: (Ord lb, Ord vn) => ApplyModifier lb vn
- makeVmod20 :: (Eq lb, Show lb, Eq vn, Show vn) => ApplyModifier lb vn
- makeVmod22 :: (Ord lb, Ord vn) => ApplyModifier lb vn
- makeVmodN1 :: (Ord lb, Ord vn) => ApplyModifier lb vn
- data DatatypeSub ex lb vn supvt subvt = DatatypeSub {
- trelSup :: DatatypeVal ex supvt lb vn
- trelSub :: DatatypeVal ex subvt lb vn
- trelToSup :: subvt -> supvt
- trelToSub :: supvt -> Maybe subvt
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.
forall vt. Datatype (DatatypeVal ex vt lb vn) |
typeName :: Datatype ex lb vn -> ScopedName Source #
Get type name 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 Text Source #
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:
- to support the general datatype entailment rules defined by the RDF semantics specification, and
- 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.
DatatypeVal | |
|
getDTMod :: ScopedName -> DatatypeVal ex vt lb vn -> Maybe (DatatypeMod vt lb vn) Source #
Return the named datatype value modifier, if it exists.
getDTRel :: ScopedName -> DatatypeVal ex vt lb vn -> Maybe (DatatypeRel vt) Source #
Return the named datatype relation, if it exists.
tvalMkCanonicalForm :: DatatypeVal ex vt lb vn -> Text -> Maybe Text Source #
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 Text
.
data DatatypeRel vt Source #
Datatype for a named relation on values of a datatype.
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] -> Bool Source #
Type for datatype relation predicate: accepts a list of values and determines whether or not they satisfy the relation.
:: 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 |
-> ((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:
|
-> DatatypeRelFn vt | The return value can be used as the
|
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 a Source #
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 a Source #
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 a Source #
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 a Source #
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.
DatatypeMod | |
|
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 vn Source #
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 vn Source #
Null datatype value modifier
makeVmod11inv :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[x,y] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
andy
are in the appropriate relationship. - is
[y] -> [x]
, used to perform the calculation in a forward direction. - 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).
- is
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 :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[x,y] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
andy
are in the appropriate relationship. - is
[x]
->[y]
, used to perform the calculation.
- is
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 :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[x,y,z] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
,y
andz
are in the appropriate relationship. - is
[y,z] -> [x]
, used to perform the calculation in a forward direction. - is
[x,z] -> [y]
, used to run the calculation backwards to determine the first input argument - is
[x,y] -> [z]
, used to run the calculation backwards to determine the second input argument
- is
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 :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[x,y,z] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
,y
andz
are in the appropriate relationship. - is
[y,z] -> [x]
, used to perform the calculation in a forward direction.
- is
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 vn Source #
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:
- is
[x,y] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
andy
are in the appropriate relationship.
- is
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 :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[w,x,y,z] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifw
,x
,y
andz
are in the appropriate relationship. - is
[y,z] -> [w,x]
, used to perform the calculation given two input values.
- is
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 :: (Ord lb, Ord vn) => ApplyModifier lb vn Source #
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:
- is
[x,y...] -> [?]
, used as a filter (i.e. not creating any new variable bindings), returning a non-empty list ifx
andy...
are in the appropriate relationship. - is
[y...] -> [x]
, used to perform the calculation.
- is
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
DatatypeSub | |
|