Chris@0
|
1 /* $Id$
|
Chris@0
|
2
|
Chris@0
|
3 Part of SWI-Prolog
|
Chris@0
|
4
|
Chris@0
|
5 Author: Jan Wielemaker
|
Chris@0
|
6 E-mail: jan@swi.psy.uva.nl
|
Chris@0
|
7 WWW: http://www.swi-prolog.org
|
Chris@0
|
8 Copyright (C): 1985-2002, University of Amsterdam
|
Chris@0
|
9
|
Chris@0
|
10 This program is free software; you can redistribute it and/or
|
Chris@0
|
11 modify it under the terms of the GNU General Public License
|
Chris@0
|
12 as published by the Free Software Foundation; either version 2
|
Chris@0
|
13 of the License, or (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 This program is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU Lesser General Public
|
Chris@0
|
21 License along with this library; if not, write to the Free Software
|
Chris@0
|
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
Chris@0
|
23
|
Chris@0
|
24 As a special exception, if you link this library with other files,
|
Chris@0
|
25 compiled with a Free Software compiler, to produce an executable, this
|
Chris@0
|
26 library does not by itself cause the resulting executable to be covered
|
Chris@0
|
27 by the GNU General Public License. This exception does not however
|
Chris@0
|
28 invalidate any other reasons why the executable file might be covered by
|
Chris@0
|
29 the GNU General Public License.
|
Chris@0
|
30 */
|
Chris@0
|
31
|
Chris@0
|
32
|
Chris@0
|
33 :- module(rdf_portray,
|
Chris@0
|
34 [ rdf_portray_as/1, % +Style
|
Chris@0
|
35 rdf_portray_lang/1 % +Lang
|
Chris@0
|
36 ]).
|
Chris@0
|
37 :- use_module(library(semweb/rdf_db)).
|
Chris@0
|
38 :- use_module(library(semweb/rdfs)).
|
Chris@0
|
39 :- use_module(library(error)).
|
Chris@0
|
40
|
Chris@0
|
41 /** <module> Portray RDF resources
|
Chris@0
|
42
|
Chris@0
|
43 This module defines rules for user:portray/1 to help tracing and
|
Chris@0
|
44 debugging RDF resources by printing them in a more concise
|
Chris@0
|
45 representation and optionally adding comment from the label field to het
|
Chris@0
|
46 the user interpreting the URL. The main predicates are:
|
Chris@0
|
47
|
Chris@0
|
48 * rdf_portray_as/1 defines the overall style
|
Chris@0
|
49 * rdf_portray_lang/1 selects languages for extracting label comments
|
Chris@0
|
50
|
Chris@0
|
51 @tbd Define alternate predicate to use for providing a comment
|
Chris@0
|
52 @tbd Use type if there is no meaningful label?
|
Chris@0
|
53 @tbd Smarter guess whether or not the local identifier might be
|
Chris@0
|
54 meaningful to the user without a comment. I.e. does it look
|
Chris@0
|
55 `word-like'?
|
Chris@0
|
56 */
|
Chris@0
|
57
|
Chris@0
|
58 :- dynamic
|
Chris@0
|
59 style/1,
|
Chris@0
|
60 lang/1.
|
Chris@0
|
61
|
Chris@0
|
62 %% rdf_portray_as(+Style) is det.
|
Chris@0
|
63 %
|
Chris@0
|
64 % Set the style used to portray resources. Style is one of:
|
Chris@0
|
65 %
|
Chris@0
|
66 % * ns:id
|
Chris@0
|
67 % Write as NS:ID, compatible with what can be handed to
|
Chris@0
|
68 % the rdf predicates. This is the default.
|
Chris@0
|
69 %
|
Chris@0
|
70 % * writeq
|
Chris@0
|
71 % Use quoted write of the full resource.
|
Chris@0
|
72 %
|
Chris@0
|
73 % * ns:label
|
Chris@0
|
74 % Write namespace followed by the label. This format
|
Chris@0
|
75 % cannot be handed to rdf/3 and friends, but can be
|
Chris@0
|
76 % useful if resource-names are meaningless identifiers.
|
Chris@0
|
77 %
|
Chris@0
|
78 % * ns:id=label
|
Chris@0
|
79 % This combines ns:id with ns:label, providing both human
|
Chris@0
|
80 % readable output and output that can be pasted into the
|
Chris@0
|
81 % commandline.
|
Chris@0
|
82
|
Chris@0
|
83 rdf_portray_as(Style) :-
|
Chris@0
|
84 must_be(oneof([writeq, ns:id, ns:label, ns:id=label]), Style),
|
Chris@0
|
85 retractall(style(_)),
|
Chris@0
|
86 assert(style(Style)).
|
Chris@0
|
87
|
Chris@0
|
88 %% rdf_portray_lang(+Lang) is det.
|
Chris@0
|
89 %
|
Chris@0
|
90 % If Lang is a list, set the list or preferred languages. If it is
|
Chris@0
|
91 % a single atom, push this language as the most preferred
|
Chris@0
|
92 % language.
|
Chris@0
|
93
|
Chris@0
|
94 rdf_portray_lang(Lang) :-
|
Chris@0
|
95 ( is_list(Lang)
|
Chris@0
|
96 -> must_be(list(atom), Lang),
|
Chris@0
|
97 retractall(lang(_)),
|
Chris@0
|
98 forall(member(L,Lang), assert(lang(L)))
|
Chris@0
|
99 ; must_be(atom, Lang),
|
Chris@0
|
100 asserta(lang(Lang))
|
Chris@0
|
101 ).
|
Chris@0
|
102
|
Chris@0
|
103 try_lang(L) :- lang(L).
|
Chris@0
|
104 try_lang(_).
|
Chris@0
|
105
|
Chris@0
|
106
|
Chris@0
|
107 :- multifile
|
Chris@0
|
108 user:portray/1.
|
Chris@0
|
109
|
Chris@0
|
110 user:portray(URL) :-
|
Chris@0
|
111 atom(URL),
|
Chris@0
|
112 sub_atom(URL, 0, _, _, 'http://'), !,
|
Chris@0
|
113 ( style(Style)
|
Chris@0
|
114 -> true
|
Chris@0
|
115 ; Style = ns:id
|
Chris@0
|
116 ),
|
Chris@0
|
117 portray_url(Style, URL).
|
Chris@0
|
118 user:portray(URL) :-
|
Chris@0
|
119 atom(URL),
|
Chris@0
|
120 atom_concat('__file://', URL2, URL),
|
Chris@0
|
121 sub_atom(URL2, S, _, A, #),
|
Chris@0
|
122 sub_atom(URL2, _, A, 0, Local),
|
Chris@0
|
123 sub_atom(URL2, 0, S, _, Path),
|
Chris@0
|
124 file_base_name(Path, Base),
|
Chris@0
|
125 format('__~w#~w', [Base, Local]).
|
Chris@0
|
126
|
Chris@0
|
127 portray_url(writeq, URL) :-
|
Chris@0
|
128 writeq(URL).
|
Chris@0
|
129 portray_url(ns:id, URL) :-
|
Chris@0
|
130 ( rdf_global_id(NS:Id, URL)
|
Chris@0
|
131 -> writeq(NS:Id)
|
Chris@0
|
132 ; writeq(URL)
|
Chris@0
|
133 ).
|
Chris@0
|
134 portray_url(ns:id=label, URL) :-
|
Chris@0
|
135 ( rdf_global_id(NS:Id, URL)
|
Chris@0
|
136 -> Value = NS:Id
|
Chris@0
|
137 ; Value = URL
|
Chris@0
|
138 ),
|
Chris@0
|
139 ( Id \== '',
|
Chris@0
|
140 ( ( try_lang(Lang),
|
Chris@0
|
141 rdf_has(URL, rdfs:label, literal(lang(Lang, Label)))
|
Chris@0
|
142 -> nonvar(Lang),
|
Chris@0
|
143 \+ label_is_id(Label, Id)
|
Chris@0
|
144 )
|
Chris@0
|
145 -> format('~q/*"~w"@~w*/', [Value, Label, Lang])
|
Chris@0
|
146 ; rdf_has(URL, rdfs:label, literal(type(Type, Label))),
|
Chris@0
|
147 nonvar(Type),
|
Chris@0
|
148 \+ label_is_id(Label, Id)
|
Chris@0
|
149 -> ( rdf_global_id(TNS:TId, Type)
|
Chris@0
|
150 -> TVal = TNS:TId
|
Chris@0
|
151 ; TVal = Type
|
Chris@0
|
152 ),
|
Chris@0
|
153 format('~q/*"~w"^^~w*/', [Value, Label, TVal])
|
Chris@0
|
154 ; rdf_has(URL, rdfs:label, literal(Label)),
|
Chris@0
|
155 atom(Label),
|
Chris@0
|
156 Label \== Id
|
Chris@0
|
157 -> format('~q/*"~w"*/', [Value, Label])
|
Chris@0
|
158 )
|
Chris@0
|
159 -> true
|
Chris@0
|
160 ; writeq(Value)
|
Chris@0
|
161 ).
|
Chris@0
|
162 portray_url(ns:label, URL) :-
|
Chris@0
|
163 rdfs_ns_label(URL, Label),
|
Chris@0
|
164 write(Label).
|
Chris@0
|
165
|
Chris@0
|
166 label_is_id(_, Var) :-
|
Chris@0
|
167 var(Var), !, fail.
|
Chris@0
|
168 label_is_id(Label, Label) :- !.
|
Chris@0
|
169 label_is_id(L0, L1) :-
|
Chris@0
|
170 downcase_atom(L0, Lwr),
|
Chris@0
|
171 downcase_atom(L1, Lwr).
|
Chris@0
|
172
|