skos/commit

Added SKOS files

authorJan Wielemaker
Mon Nov 22 16:43:02 2010 +0100
committerJan Wielemaker
Mon Nov 22 16:43:02 2010 +0100
commite5a90381821cbe75d314eb6ea91e645b88d8a359
treecb6baa489062c0e660df36688145c49117918121
parentb486a138f754fcf8621d1abcdaae7d34dd889ab3
Diff style: patch stat
diff --git a/config-available/skos.pl b/config-available/skos.pl
index d49cd20..ce166f6 100644
--- a/config-available/skos.pl
+++ b/config-available/skos.pl
@@ -1,5 +1,13 @@
 :- module(conf_skos, []).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_library)).
 
-/** <module> SKOS schema and libraries
+/** <module> Provide SKOS schema and namespace
+
+This module provides the SKOS schema and   the  prefix =skos= for use in
+Prolog.
 */
 
+:- rdf_register_ns(foaf, 'http://www.w3.org/2004/02/skos/core#').
+:- rdf_attach_library(skos(rdf)).
+:- rdf_load_library(skos).
diff --git a/lib/skos/concept.pl b/lib/skos/concept.pl
new file mode 100644
index 0000000..9b2e6d8
--- /dev/null
+++ b/lib/skos/concept.pl
@@ -0,0 +1,136 @@
+:- module(ag_skos_concept, [
+			    assert_concept_stats/2
+			   ]).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(amalgame/map)).
+:- use_module(vocabularies).
+
+assert_concept_stats(Voc, Graph) :-
+	ground(Voc),
+	ground(Graph),
+	(   rdf_graph(Graph) -> rdf_unload(Graph); true),
+	topconcepts(Voc, TopConcepts),
+	forall(member(Top, TopConcepts),
+	       assert_subtree_stats(Top, [graph(Graph)], _Stats)
+	      ).
+
+mapped(Concept, Mapped) :-
+	(   ( has_map([Concept, _], _, _)
+	    ; has_map([_, Concept], _, _)
+	    )
+	->  Mapped = 1
+	;   Mapped = 0
+	),!.
+
+
+assert_subtree_stats(Root, Options, []) :-
+	option(path(Path), Options),
+        memberchk(Root, Path), % Oops, cycle, done this already
+        !,
+        debug(stats, 'Cycle detected for ~w~n', [Root]),
+        rdf_assert(Root, amalgame:cycle, literal(true), stats),
+	fail.
+
+assert_subtree_stats(Root, Options, []) :-
+	rdf(Root, amalgame:height, _, Graph),% oops, multiple parents, done this already
+	option(graph(Graph), Options, amalgame_concepts),
+	!,
+	fail.
+
+assert_subtree_stats(Root, Options, Stats) :-
+	\+ has_child(Root, _), % No child, this is a leave node ...
+	option(graph(Graph), Options, amalgame_concepts),
+	option(depth(Depth), Options, -1),
+
+	mapped(Root, Mapped),
+	rdf_assert(Root, amalgame:height,    literal(type(xsd:int, 0)),      Graph),
+	rdf_assert(Root, amalgame:depth,     literal(type(xsd:int, Depth)),  Graph),
+	rdf_assert(Root, amalgame:isMapped, literal(type(xsd:int, Mapped)), Graph),
+
+	Stats = [max_height(0),
+		 avg_height(0.0),
+		 min_height(0),
+		 size(1),
+		 mapped(Mapped)
+		],
+	!.
+
+
+
+assert_subtree_stats(Root, Options, Stats) :-
+	% Assume we have a normal Concept with #children > 0
+	option(depth(Depth), Options, 0),
+	option(graph(Graph), Options, amalgame_concepts),
+	option(path(Path), Options, []),
+	NewPath = [Root|Path],
+	succ(Depth, NewDepth),
+
+	merge_options([depth(NewDepth), path(NewPath)], Options, ChildOptions),
+
+
+	findall(Child, has_child(Root, Child), Children),
+	findall(ChildStat,
+		(member(Child, Children),
+		 assert_subtree_stats(Child, ChildOptions, ChildStat)
+		),
+	       ChildStatsList
+	       ),
+	mapped(Root, Mapped),
+	rdf_assert(Root, amalgame:isMapped, literal(type(xsd:int, Mapped)), Graph),
+	calculate_child_stats([mapped(Mapped)|ChildStatsList], Stats),
+	assert_stats(Root, Options, [depth(Depth)|Stats]),
+	!.
+
+assert_stats(_Node, _, []).
+assert_stats(Node, Options, Stats) :-
+	option(graph(Graph), Options, amalgame_concepts),
+        debug(stats, 'Stats: ~w~n', [Stats]),
+        option(depth(Depth), Stats),
+        option(size(Size), Stats),
+        option(max_height(MaxHeight), Stats),
+        option(min_height(MinHeight), Stats),
+        option(avg_height(AvgHeight), Stats),
+	option(mapped(Mapped), Stats),
+        rdf_assert(Node, amalgame:depth,     literal(type(xsd:int, Depth)),     Graph),
+        rdf_assert(Node, amalgame:size,      literal(type(xsd:int, Size)),      Graph),
+        rdf_assert(Node, amalgame:maxHeight, literal(type(xsd:int, MaxHeight)), Graph),
+        rdf_assert(Node, amalgame:minHeight, literal(type(xsd:int, MinHeight)), Graph),
+        rdf_assert(Node, amalgame:avgHeight, literal(type(xsd:float, AvgHeight)), Graph),
+        rdf_assert(Node, amalgame:mapped,    literal(type(xsd:int, Mapped)), Graph).
+
+calculate_child_stats([[]], []).
+calculate_child_stats(List, Stats) :-
+        flatten(List, FlatList),
+        findall(Max, member(max_height(Max), FlatList), Maxes),
+        max_list(Maxes, MaxHeight),
+
+        findall(Min, member(min_height(Min), FlatList), Mins),
+        min_list(Mins, MinHeight),
+
+        findall(Avg, member(avg_height(Avg), FlatList), Avgs),
+        sumlist(Avgs, AvgSum),
+        length(Avgs, Length),
+        AvgHeight is AvgSum/Length,
+
+        findall(Size, member(size(Size), FlatList), Sizes),
+        sumlist(Sizes, SizeSum),
+
+	findall(Mapped, member(mapped(Mapped), FlatList), Mappeds),
+        sumlist(Mappeds, MappedSum),
+
+        AvgHeight1 is AvgHeight + 1,
+        MaxHeight1 is MaxHeight + 1,
+        MinHeight1 is MinHeight + 1,
+        TotalSize  is SizeSum + 1,
+
+        Stats=[max_height(MaxHeight1),
+               min_height(MinHeight1),
+               avg_height(AvgHeight1),
+               size(TotalSize),
+	       mapped(MappedSum)
+              ].
+
+has_child(Root, Child) :-
+	rdf_has(Child, skos:broader, Root).
+
+
diff --git a/lib/skos/vocabularies.pl b/lib/skos/vocabularies.pl
new file mode 100644
index 0000000..e50d2f4
--- /dev/null
+++ b/lib/skos/vocabularies.pl
@@ -0,0 +1,262 @@
+:- module(am_skosvocs,
+          [
+	   skos_label/2,
+	   skos_label/3,
+	   topconcepts/2,
+	   voc_get_computed_props/2,
+	   voc_clear_stats/1,
+	   voc_ensure_stats/1,
+	   voc_partition/4,
+	   voc_delete_derived/0
+          ]).
+
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/html_write)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(library(semweb/rdf_portray)).
+
+:- use_module(library(amalgame/map)).
+:- use_module(library(amalgame/opm)).
+
+/** <module> Compute and store vocabulary-oriented statistics as RDF.
+
+Currently supported statistical properties include:
+* numberOfConcepts(xsd:int)
+* numberOfPrefLabels(xsd:int)
+* numberOfAltLabels(xsd:int)
+* numberOfMappedConcepts(xsd:int)
+
+Side effect: These statistics will also be asserted as RDF
+triples to the 'amalgame_vocs' named graph, using similarly named
+properties with the 'amalgame:' namespace prefix. These asserted
+triples will be used in subsequent calls for efficiency reasons.
+
+See also http_clear_cache/1.
+
+@author Jacco van Ossenbruggen
+*/
+
+%%	voc_get_computed_props(+Voc, -Props) is det.
+%
+%	Collect all amalgame properties Props of Voc that have been
+%	already computed and asserted in the amalgame named graph.
+%
+
+voc_get_computed_props(Voc, Props) :-
+	findall([PropLn, Value],
+		(   rdf(Voc, Prop, Value, amalgame_vocs),
+		    rdf_global_id(amalgame:PropLn, Prop)
+		),
+		GraphProps
+	       ),
+	maplist(=.., Props, GraphProps).
+
+voc_clear_stats(Graph) :-
+	(   rdf_graph(Graph)
+	->  rdf_unload(amalgame_vocs)
+	;   true),
+	print_message(informational, map(cleared, 'vocabulary statistics', amalgame_vocs, all)).
+
+voc_delete_derived :-
+	findall(Voc, rdf(Voc, rdf:type, amalgame:'DerivedConceptScheme'), Derived),
+	forall(member(Voc, Derived),
+	       ( rdf_unload(Voc),
+		 print_message(informational, map(cleared, 'vocabulary', Voc, 1))
+	       )
+	      ).
+
+
+%%	voc_ensure_stats(+Type) is det.
+%
+%	Ensures that the statistical properties of Type are asserted in
+%	the amalgame graph.
+
+voc_ensure_stats(all) :-
+	findall(V, rdfs_individual_of(V, skos:'ConceptScheme'), Vocs),!,
+	length(Vocs, N),
+	print_message(informational, map(found, 'SKOS vocabularies (ConceptSchemes)', repository, N)),
+
+	forall(member(V, Vocs),voc_ensure_stats(all(V))).
+
+voc_ensure_stats(all(V)) :-
+	voc_ensure_stats(numberOfConcepts(V)),
+	voc_ensure_stats(numberOfPrefLabels(V)),
+	voc_ensure_stats(numberOfAltLabels(V)),
+	voc_ensure_stats(numberOfMappedConcepts(V)).
+
+
+voc_ensure_stats(numberOfConcepts(Voc)) :-
+	(   rdf(Voc,amalgame:numberOfConcepts, literal(type(_, Count)))
+	->  true
+	;   count_concepts(Voc, Count),
+	    assert_voc_props(Voc:[numberOfConcepts(literal(type('http://www.w3.org/2001/XMLSchema#int', Count)))])
+	),!.
+
+voc_ensure_stats(numberOfPrefLabels(Voc)) :-
+	(   rdf(Voc,amalgame:numberOfPrefLabels, literal(type(_, Count)))
+	->  true
+	;   count_prefLabels(Voc, Count),
+	    assert_voc_props(Voc:[numberOfPrefLabels(literal(type('http://www.w3.org/2001/XMLSchema#int', Count)))])
+	),!.
+
+voc_ensure_stats(numberOfAltLabels(Voc)) :-
+	(   rdf(Voc,amalgame:numberOfAltLabels, literal(type(_, Count)))
+	->  true
+	;   count_altLabels(Voc, Count),
+	    assert_voc_props(Voc:[numberOfAltLabels(literal(type('http://www.w3.org/2001/XMLSchema#int', Count)))])
+	),!.
+
+voc_ensure_stats(numberOfMappedConcepts(Voc)) :-
+	(   rdf(Voc,amalgame:numberOfMappedConcepts, literal(type(_, Count)))
+	->  true
+	;   count_mapped_concepts(Voc, Count),
+	    assert_voc_props(Voc:[numberOfMappedConcepts(literal(type('http://www.w3.org/2001/XMLSchema#int', Count)))])
+	),!.
+
+assert_voc_props([]).
+assert_voc_props([Head|Tail]) :-
+	assert_voc_props(Head),
+	assert_voc_props(Tail),!.
+
+assert_voc_props(Voc:Props) :-
+	rdf_equal(amalgame:'', NS),
+	(   rdfs_individual_of(Voc, skos:'ConceptScheme')
+	->  true
+	;   rdf_assert(Voc, rdf:type, skos:'ConceptScheme', amalgame_vocs)
+	),
+	forall(member(M,Props),
+	       (   M =.. [PropName, Value],
+		   format(atom(URI), '~w~w', [NS,PropName]),
+		   rdf_assert(Voc, URI, Value, amalgame_vocs)
+	       )).
+
+count_concepts(Voc, Count) :-
+	findall(Concept,
+		rdf(Concept, skos:inScheme, Voc),
+		Concepts),
+	length(Concepts, Count),
+	print_message(informational, map(found, 'SKOS Concepts', Voc, Count)).
+
+
+count_prefLabels(Voc, Count) :-
+	findall(Label,
+		(   rdf(Concept, skos:inScheme, Voc),
+		    rdf_has(Concept, skos:prefLabel, literal(Label))
+		),
+		Labels),
+	length(Labels, Count),
+	print_message(informational, map(found, 'SKOS preferred labels', Voc, Count)).
+
+count_altLabels(Voc, Count) :-
+	findall(Label,
+		(   rdf(Concept, skos:inScheme, Voc),
+		    rdf_has(Concept, skos:altLabel, literal(Label))
+		),
+		Labels),
+	length(Labels, Count),
+	print_message(informational, map(found, 'SKOS alternative labels', Voc, Count)).
+
+count_mapped_concepts(Voc, Count) :-
+	findall(C,
+		(   rdf(C, skos:inScheme, Voc),
+		    (  	has_map_chk([C,_], _, _)
+		    ;	has_map_chk([_,C], _, _)
+		    )
+                ),
+		Concepts),
+	sort(Concepts, Sorted),
+	length(Sorted, Count),
+	print_message(informational, map(found, 'SKOS mapped concepts', Voc, Count)).
+
+voc_partition(Request, Voc, PartitionType, Partition) :-
+	findall(C, rdf(C, skos:inScheme, Voc), Concepts),
+	classify_concepts(Request, Concepts, Voc, PartitionType, [], Partition).
+
+
+classify_concepts(Req, [], Voc, _PartitionType, Partition, Partition) :-
+	rdf_bnode(Process),
+	forall(member(SubVoc, Partition),
+	       (
+		   rdf_assert(Process, rdfs:label, literal('Amalgame vocabulary partitioning process'), SubVoc),
+		   opm_was_generated_by(Process, SubVoc, SubVoc, [was_derived_from([Voc]), request(Req)])
+	       )).
+classify_concepts(Req, [H|T], Voc, PartitionType, Accum, Result) :-
+	classify_concept(H, Voc, PartitionType, SubVocURI, SubVocLabelURI),
+	(   member(SubVocURI, Accum)
+	->  NewAccum = Accum
+	;   make_subvoc(Voc, SubVocURI, SubVocLabelURI),
+	    NewAccum = [SubVocURI|Accum]
+	),
+	classify_concepts(Req, T, Voc, PartitionType, NewAccum, Result).
+
+make_subvoc(Voc, SubVoc, PortrayURI) :-
+	rdf_display_label(Voc,  VocL),
+	format(atom(SubVocLabel), '~w (~p)', [VocL, PortrayURI]),
+
+	(   rdf_graph(SubVoc) -> rdf_unload(SubVoc); true),
+
+	rdf_assert(SubVoc, rdfs:label, literal(SubVocLabel), SubVoc),
+	rdf_assert(SubVoc, rdf:type, amalgame:'NoAlignmentGraph', SubVoc),
+	rdf_assert(SubVoc, rdf:type, amalgame:'DerivedConceptScheme', SubVoc).
+
+classify_concept(C, Voc, mapped, SubVoc, Type) :-
+	(   (has_map_chk([C, _],_ ,_); has_map_chk([_,C], _, _))
+	->  Type = mapped
+	;   Type = unmapped
+	),
+	assign_to_subvoc(C, Voc, Type, SubVoc).
+
+classify_concept(C, Voc, type, SubVoc, Type) :-
+	findall(Type,
+		(   rdfs_individual_of(C, Type)
+		),
+		AllTypes),
+	findall(Type,
+		(   member(Type, AllTypes),
+		    \+ rdf_equal(Type, skos:'Concept'),
+		    \+ (rdfs_subclass_of(SubType, Type),
+			SubType \= Type,
+			member(SubType, AllTypes)
+		       )
+		),
+		Types),
+	Types = [Type|_],
+	assign_to_subvoc(C, Voc, Type, SubVoc).
+
+assign_to_subvoc(C, Voc, Type, SubVoc) :-
+	format(atom(Suffix), '_~p',  [Type]),
+	atom_concat(Voc, Suffix, SubVoc),
+	rdf_assert(C, skos:inScheme, SubVoc, SubVoc).
+
+
+%%	skos_label(+Concept, -Label, -Options) is det.
+%
+%	Return the most appropriate Label for Concept.
+%       May or may not include specified language
+%      (use ISO code) (code by Victor)
+
+skos_label(Concept, Label, Options) :-
+	memberchk(preflang(PrefLang),Options),
+	rdf_has(Concept, skos:prefLabel, literal(lang(PrefLang, Label))),!.
+skos_label(Concept, Label, Options) :-
+	memberchk(preflang(PrefLang),Options),
+	rdf_has(Concept, skos:altLabel, literal(lang(PrefLang, Label))),!.
+
+skos_label(Concept, Label, _Options) :-
+	rdf_has(Concept, skos:prefLabel, literal(lang(_, Label))),!.
+skos_label(Concept, Label, _Options) :-
+	rdf_has(Concept, skos:altLabel, literal(lang(_, Label))),!.
+
+skos_label(Concept, Label, _) :-
+	rdfs_label(Concept, Label),!.
+skos_label(Concept, Label, _) :-
+	format(atom(Label), '<~p>', [Concept]),!.
+
+% for backwards compatibility
+skos_label(Concept, Label):-
+	skos_label(Concept, Label, []).
+
+topconcepts(Voc, TopConcepts) :-
+	findall(Top, rdf_has(Voc, skos:hasTopConcept, Top), TopConcepts).
diff --git a/rdf/base/skos.rdf b/rdf/base/skos.rdf
new file mode 100644
index 0000000..54927ab
--- /dev/null
+++ b/rdf/base/skos.rdf
@@ -0,0 +1,467 @@
+<?xml version="1.0" encoding="utf-8"?>
+<rdf:RDF xmlns:dct="http://purl.org/dc/terms/"
+  xmlns:owl="http://www.w3.org/2002/07/owl#" xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+  xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#" xmlns:skos="http://www.w3.org/2004/02/skos/core#"
+  xml:base="http://www.w3.org/2004/02/skos/core">
+  <!-- This schema represents a formalisation of a subset of the semantic conditions 
+    described in the SKOS Reference document. XML comments of the form Sn are used to 
+    indicate the semantic conditions that are being expressed. Comments of the form 
+    [Sn] refer to assertions that are, strictly speaking, redundant as they follow 
+    from the RDF(S) or OWL semantics.
+    
+    A number of semantic conditions are *not* expressed formally in this schema. These are:
+    
+    S12
+    S13
+    S14
+    S27
+    S36
+    S46
+    
+    For the conditions listed above, rdfs:comments are used to indicate the conditions.
+    
+   -->
+  <owl:Ontology rdf:about="http://www.w3.org/2004/02/skos/core">
+    <dct:title xml:lang="en">SKOS Vocabulary</dct:title>
+    <dct:contributor>Dave Beckett</dct:contributor>
+    <dct:contributor>Nikki Rogers</dct:contributor>
+    <dct:contributor>Participants in W3C's Semantic Web Deployment Working Group.</dct:contributor>
+    <dct:description xml:lang="en">An RDF vocabulary for describing the basic structure and content of concept schemes such as thesauri, classification schemes, subject heading lists, taxonomies, 'folksonomies', other types of controlled vocabulary, and also concept schemes embedded in glossaries and terminologies.</dct:description>
+    <dct:creator>Alistair Miles</dct:creator>
+    <dct:creator>Sean Bechhofer</dct:creator>
+    <rdfs:seeAlso rdf:resource="http://www.w3.org/TR/skos-reference/"/>
+  </owl:Ontology>
+  <rdf:Description rdf:about="#Concept">
+    <rdfs:label xml:lang="en">Concept</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">An idea or notion; a unit of thought.</skos:definition>
+    <!-- S1 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#Class"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#ConceptScheme">
+    <rdfs:label xml:lang="en">Concept Scheme</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A set of concepts, optionally including statements about semantic relationships between those concepts.</skos:definition>
+    <skos:scopeNote xml:lang="en">A concept scheme may be defined to include concepts from different sources.</skos:scopeNote>
+    <skos:example xml:lang="en">Thesauri, classification schemes, subject heading lists, taxonomies, 'folksonomies', and other types of controlled vocabulary are all examples of concept schemes. Concept schemes are also embedded in glossaries and terminologies.</skos:example>
+    <!-- S2 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#Class"/>
+    <!-- S9 -->
+    <owl:disjointWith rdf:resource="#Concept"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#Collection">
+    <rdfs:label xml:lang="en">Collection</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A meaningful collection of concepts.</skos:definition>
+    <skos:scopeNote xml:lang="en">Labelled collections can be used where you would like a set of concepts to be displayed under a 'node label' in the hierarchy.</skos:scopeNote>
+    <!-- S28 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#Class"/>
+    <!-- S37 -->
+    <owl:disjointWith rdf:resource="#Concept"/>
+    <!-- S37 -->
+    <owl:disjointWith rdf:resource="#ConceptScheme"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#OrderedCollection">
+    <rdfs:label xml:lang="en">Ordered Collection</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">An ordered collection of concepts, where both the grouping and the ordering are meaningful.</skos:definition>
+    <skos:scopeNote xml:lang="en">Ordered collections can be used where you would like a set of concepts to be displayed in a specific order, and optionally under a 'node label'.</skos:scopeNote>
+    <!-- S28 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#Class"/>
+    <!-- S29 -->
+    <rdfs:subClassOf rdf:resource="#Collection"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#inScheme">
+    <rdfs:label xml:lang="en">is in scheme</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a resource (for example a concept) to a concept scheme in which it is included.</skos:definition>
+    <skos:scopeNote xml:lang="en">A concept may be a member of more than one concept scheme.</skos:scopeNote>
+    <!-- S3 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S4 -->
+    <rdfs:range rdf:resource="#ConceptScheme"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#hasTopConcept">
+    <rdfs:label xml:lang="en">has top concept</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates, by convention, a concept scheme to a concept which is topmost in the broader/narrower concept hierarchies for that scheme, providing an entry point to these hierarchies.</skos:definition>
+    <!-- S3 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S5 -->
+    <rdfs:domain rdf:resource="#ConceptScheme"/>
+    <!-- S6 -->
+    <rdfs:range rdf:resource="#Concept"/>
+    <!-- S8 -->
+    <owl:inverseOf rdf:resource="#topConceptOf"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#topConceptOf">
+    <rdfs:label xml:lang="en">is top concept in scheme</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a concept to the concept scheme that it is a top level concept of.</skos:definition>
+    <!-- S3 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S7 -->
+    <rdfs:subPropertyOf rdf:resource="#inScheme"/>
+    <!-- S8 -->
+    <owl:inverseOf rdf:resource="#hasTopConcept"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+    <rdfs:domain rdf:resource="#Concept"/>
+    <rdfs:range rdf:resource="#ConceptScheme"/> 
+  </rdf:Description>
+  <rdf:Description rdf:about="#prefLabel">
+    <rdfs:label xml:lang="en">preferred label</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">The preferred lexical label for a resource, in a given language.</skos:definition>
+    <!-- S10 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S11 -->
+    <rdfs:subPropertyOf rdf:resource="http://www.w3.org/2000/01/rdf-schema#label"/>
+    <!-- S14 (not formally stated) -->
+    <rdfs:comment xml:lang="en">A resource has no more than one value of skos:prefLabel per language tag.</rdfs:comment>
+    <!-- S12 (not formally stated) -->
+    <rdfs:comment xml:lang="en">The range of skos:prefLabel is the class of RDF plain literals.</rdfs:comment>
+    <!-- S13 (not formally stated) -->
+    <rdfs:comment xml:lang="en">skos:prefLabel, skos:altLabel and skos:hiddenLabel are pairwise
+      disjoint properties.</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#altLabel">
+    <rdfs:label xml:lang="en">alternative label</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">An alternative lexical label for a resource.</skos:definition>
+    <skos:example xml:lang="en">Acronyms, abbreviations, spelling variants, and irregular plural/singular forms may be included among the alternative labels for a concept. Mis-spelled terms are normally included as hidden labels (see skos:hiddenLabel).</skos:example>
+    <!-- S10 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S11 -->
+    <rdfs:subPropertyOf rdf:resource="http://www.w3.org/2000/01/rdf-schema#label"/>
+    <!-- S12 (not formally stated) -->
+    <rdfs:comment xml:lang="en">The range of skos:altLabel is the class of RDF plain literals.</rdfs:comment>
+    <!-- S13 (not formally stated) -->
+    <rdfs:comment xml:lang="en">skos:prefLabel, skos:altLabel and skos:hiddenLabel are pairwise disjoint properties.</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#hiddenLabel">
+    <rdfs:label xml:lang="en">hidden label</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A lexical label for a resource that should be hidden when generating visual displays of the resource, but should still be accessible to free text search operations.</skos:definition>
+    <!-- S10 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S11 -->
+    <rdfs:subPropertyOf rdf:resource="http://www.w3.org/2000/01/rdf-schema#label"/>
+    <!-- S12 (not formally stated) -->
+    <rdfs:comment xml:lang="en">The range of skos:hiddenLabel is the class of RDF plain literals.</rdfs:comment>
+    <!-- S13 (not formally stated) -->
+    <rdfs:comment xml:lang="en">skos:prefLabel, skos:altLabel and skos:hiddenLabel are pairwise disjoint properties.</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#notation">
+    <rdfs:label xml:lang="en">notation</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A notation, also known as classification code, is a string of characters such as "T58.5" or "303.4833" used to uniquely identify a concept within the scope of a given concept scheme.</skos:definition>
+    <skos:scopeNote xml:lang="en">By convention, skos:notation is used with a typed literal in the object position of the triple.</skos:scopeNote>
+    <!-- S15 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#DatatypeProperty"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#note">
+    <rdfs:label xml:lang="en">note</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A general note, for any purpose.</skos:definition>
+    <skos:scopeNote xml:lang="en">This property may be used directly, or as a super-property for more specific note types.</skos:scopeNote>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#changeNote">
+    <rdfs:label xml:lang="en">change note</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A note about a modification to a concept.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#definition">
+    <rdfs:label xml:lang="en">definition</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A statement or formal explanation of the meaning of a concept.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#editorialNote">
+    <rdfs:label xml:lang="en">editorial note</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A note for an editor, translator or maintainer of the vocabulary.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#example">
+    <rdfs:label xml:lang="en">example</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">An example of the use of a concept.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#historyNote">
+    <rdfs:label xml:lang="en">history note</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A note about the past state/use/meaning of a concept.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#scopeNote">
+    <rdfs:label xml:lang="en">scope note</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">A note that helps to clarify the meaning and/or the use of a concept.</skos:definition>
+    <!-- S16 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#AnnotationProperty"/>
+    <!-- S17 -->
+    <rdfs:subPropertyOf rdf:resource="#note"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#semanticRelation">
+    <rdfs:label xml:lang="en">is in semantic relation with</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Links a concept to a concept related by meaning.</skos:definition>
+    <skos:scopeNote xml:lang="en">This property should not be used directly, but as a super-property for all properties denoting a relationship of meaning between concepts.</skos:scopeNote>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S19 -->
+    <rdfs:domain rdf:resource="#Concept"/>
+    <!-- S20 -->
+    <rdfs:range rdf:resource="#Concept"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#broader">
+    <rdfs:label xml:lang="en">has broader</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a concept to a concept that is more general in meaning.</skos:definition>
+    <rdfs:comment xml:lang="en">Broader concepts are typically rendered as parents in a concept hierarchy (tree).</rdfs:comment>
+    <skos:scopeNote xml:lang="en">By convention, skos:broader is only used to assert an immediate (i.e. direct) hierarchical link between two conceptual resources.</skos:scopeNote>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S22 -->
+    <rdfs:subPropertyOf rdf:resource="#broaderTransitive"/>
+    <!-- S25 -->
+    <owl:inverseOf rdf:resource="#narrower"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#narrower">
+    <rdfs:label xml:lang="en">has narrower</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a concept to a concept that is more specific in meaning.</skos:definition>
+    <skos:scopeNote xml:lang="en">By convention, skos:broader is only used to assert an immediate (i.e. direct) hierarchical link between two conceptual resources.</skos:scopeNote>
+    <rdfs:comment xml:lang="en">Narrower concepts are typically rendered as children in a concept hierarchy (tree).</rdfs:comment>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S22 -->
+    <rdfs:subPropertyOf rdf:resource="#narrowerTransitive"/>
+    <!-- S25 -->
+    <owl:inverseOf rdf:resource="#broader"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#related">
+    <rdfs:label xml:lang="en">has related</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a concept to a concept with which there is an associative semantic relationship.</skos:definition>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S21 -->
+    <rdfs:subPropertyOf rdf:resource="#semanticRelation"/>
+    <!-- S23 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#SymmetricProperty"/>
+    <!-- S27 (not formally stated) -->
+    <rdfs:comment xml:lang="en">skos:related is disjoint with skos:broaderTransitive</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#broaderTransitive">
+    <rdfs:label xml:lang="en">has broader transitive</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition>skos:broaderTransitive is a transitive superproperty of skos:broader.</skos:definition>
+    <skos:scopeNote xml:lang="en">By convention, skos:broaderTransitive is not used to make assertions. Rather, the properties can be used to draw inferences about the transitive closure of the hierarchical relation, which is useful e.g. when implementing a simple query expansion algorithm in a search application.</skos:scopeNote>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S21 -->
+    <rdfs:subPropertyOf rdf:resource="#semanticRelation"/>
+    <!-- S24 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#TransitiveProperty"/>
+    <!-- S26 -->
+    <owl:inverseOf rdf:resource="#narrowerTransitive"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#narrowerTransitive">
+    <rdfs:label xml:lang="en">has narrower transitive</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition>skos:narrowerTransitive is a transitive superproperty of skos:narrower.</skos:definition>
+    <skos:scopeNote xml:lang="en">By convention, skos:narrowerTransitive is not used to make assertions. Rather, the properties can be used to draw inferences about the transitive closure of the hierarchical relation, which is useful e.g. when implementing a simple query expansion algorithm in a search application.</skos:scopeNote>
+    <!-- S18 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S21 -->
+    <rdfs:subPropertyOf rdf:resource="#semanticRelation"/>
+    <!-- S24 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#TransitiveProperty"/>
+    <!-- S26 -->
+    <owl:inverseOf rdf:resource="#broaderTransitive"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#member">
+    <rdfs:label xml:lang="en">has member</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates a collection to one of its members.</skos:definition>
+    <!-- S30 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S31 -->
+    <rdfs:domain rdf:resource="#Collection"/>
+    <!-- S32 -->
+    <rdfs:range>
+      <owl:Class>
+	<owl:unionOf rdf:parseType="Collection">
+	  <owl:Class rdf:about="#Concept"/>
+	  <owl:Class rdf:about="#Collection"/>
+	</owl:unionOf>
+      </owl:Class>
+    </rdfs:range>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#memberList">
+    <rdfs:label xml:lang="en">has member list</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates an ordered collection to the RDF list containing its members.</skos:definition>
+    <!-- S30 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S33 -->
+    <rdfs:domain rdf:resource="#OrderedCollection"/>
+    <!-- S35 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#FunctionalProperty"/>
+    <!-- S34 -->
+    <rdfs:range rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#List"/>
+    <!-- S36 (not formally stated) -->
+    <rdfs:comment xml:lang="en">For any resource, every item in the list given as the value of the
+      skos:memberList property is also a value of the skos:member property.</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#mappingRelation">
+    <rdfs:label xml:lang="en">is in mapping relation with</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">Relates two concepts coming, by convention, from different schemes, and that have comparable meanings</skos:definition>
+    <rdfs:comment xml:lang="en">These concept mapping relations mirror semantic relations, and the data model defined below is similar (with the exception of skos:exactMatch) to the data model defined for semantic relations. A distinct vocabulary is provided for concept mapping relations, to provide a convenient way to differentiate links within a concept scheme from links between concept schemes. However, this pattern of usage is not a formal requirement of the SKOS data model, and relies on informal definitions of best practice.</rdfs:comment>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S39 -->
+    <rdfs:subPropertyOf rdf:resource="#semanticRelation"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#broadMatch">
+    <rdfs:label xml:lang="en">has broader match</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">skos:broadMatch is used to state a hierarchical mapping link between two conceptual resources in different concept schemes.</skos:definition>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S40 -->
+    <rdfs:subPropertyOf rdf:resource="#mappingRelation"/>
+    <!-- S41 -->
+    <rdfs:subPropertyOf rdf:resource="#broader"/>
+    <!-- S43 -->
+    <owl:inverseOf rdf:resource="#narrowMatch"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#narrowMatch">
+    <rdfs:label xml:lang="en">has narrower match</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">skos:narrowMatch is used to state a hierarchical mapping link between two conceptual resources in different concept schemes.</skos:definition>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S40 -->
+    <rdfs:subPropertyOf rdf:resource="#mappingRelation"/>
+    <!-- S41 -->
+    <rdfs:subPropertyOf rdf:resource="#narrower"/>
+    <!-- S43 -->
+    <owl:inverseOf rdf:resource="#broadMatch"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#relatedMatch">
+    <rdfs:label xml:lang="en">has related match</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">skos:relatedMatch is used to state an associative mapping link between two conceptual resources in different concept schemes.</skos:definition>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S40 -->
+    <rdfs:subPropertyOf rdf:resource="#mappingRelation"/>
+    <!-- S41 -->
+    <rdfs:subPropertyOf rdf:resource="#related"/>
+    <!-- S44 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#SymmetricProperty"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#exactMatch">
+    <rdfs:label xml:lang="en">has exact match</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">skos:exactMatch is used to link two concepts, indicating a high degree of confidence that the concepts can be used interchangeably across a wide range of information retrieval applications. skos:exactMatch is a transitive property, and is a sub-property of skos:closeMatch.</skos:definition>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S42 -->
+    <rdfs:subPropertyOf rdf:resource="#closeMatch"/>
+    <!-- S44 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#SymmetricProperty"/>
+    <!-- S45 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#TransitiveProperty"/>
+    <!-- S46 (not formally stated) -->
+    <rdfs:comment xml:lang="en">skos:exactMatch is disjoint with each of the properties skos:broadMatch and skos:relatedMatch.</rdfs:comment>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+  <rdf:Description rdf:about="#closeMatch">
+    <rdfs:label xml:lang="en">has close match</rdfs:label>
+    <rdfs:isDefinedBy rdf:resource="http://www.w3.org/2004/02/skos/core"/>
+    <skos:definition xml:lang="en">skos:closeMatch is used to link two concepts that are sufficiently similar that they can be used interchangeably in some information retrieval applications. In order to avoid the possibility of "compound errors" when combining mappings across more than two concept schemes, skos:closeMatch is not declared to be a transitive property.</skos:definition>
+    <!-- S38 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#ObjectProperty"/>
+    <!-- S40 -->
+    <rdfs:subPropertyOf rdf:resource="#mappingRelation"/>
+    <!-- S44 -->
+    <rdf:type rdf:resource="http://www.w3.org/2002/07/owl#SymmetricProperty"/>
+    <!-- For non-OWL aware applications -->
+    <rdf:type rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
+  </rdf:Description>
+</rdf:RDF>