Chris@0
|
1 /* $Id: rdf_create.pl,v 1.13 2007/01/16 09:37:09 jan Exp $
|
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_create, []).
|
Chris@0
|
34 :- use_module(library(pce)).
|
Chris@0
|
35 :- use_module(library('semweb/rdf_db')).
|
Chris@0
|
36 :- use_module(library('semweb/rdf_edit')).
|
Chris@0
|
37 :- use_module(library(lists)).
|
Chris@0
|
38 :- use_module(library(url)).
|
Chris@0
|
39 :- use_module(rdf_rules).
|
Chris@0
|
40 :- use_module(rdf_util).
|
Chris@0
|
41
|
Chris@0
|
42 :- pce_autoload(identifier_item, library(pce_identifier_item)).
|
Chris@0
|
43 :- pce_autoload(rdfs_resource_item, rdfs_resource_item).
|
Chris@0
|
44
|
Chris@0
|
45 :- pce_begin_class(rdf_create_dialog, dialog,
|
Chris@0
|
46 "Create instance or class").
|
Chris@0
|
47
|
Chris@0
|
48 variable(role, name, get, "Role of the new individual").
|
Chris@0
|
49 variable(resource, name, get, "Context Class").
|
Chris@0
|
50 variable(client, object*, get, "Object to report to").
|
Chris@0
|
51
|
Chris@0
|
52 initialise(D, Parent:name, Role:name, Client:[object]*) :->
|
Chris@0
|
53 default(Client, @nil, Cntl),
|
Chris@0
|
54 send(D, slot, role, Role),
|
Chris@0
|
55 send(D, slot, resource, Parent),
|
Chris@0
|
56 send(D, slot, client, Cntl),
|
Chris@0
|
57 send_super(D, initialise, string('Create %s', Role?label_name)),
|
Chris@0
|
58 rdf_default_file(Parent, File, NS),
|
Chris@0
|
59 send(D, append, new(rdf_file_menu(File))),
|
Chris@0
|
60 send(D, append, new(rdf_ns_menu(NS))), % TBD: update if file changes
|
Chris@0
|
61 send(D, append, new(rdf_id_item), right),
|
Chris@0
|
62 send(D, append, new(C, button(create, message(D, create_resource)))),
|
Chris@0
|
63 send(D, append, button(done)),
|
Chris@0
|
64 send(C, default_button, @on).
|
Chris@0
|
65
|
Chris@0
|
66 done(D) :->
|
Chris@0
|
67 send(D, destroy).
|
Chris@0
|
68
|
Chris@0
|
69 cancel(D) :->
|
Chris@0
|
70 send(D, done).
|
Chris@0
|
71
|
Chris@0
|
72 create_resource(D) :->
|
Chris@0
|
73 "Create (new) resource from dialog contents"::
|
Chris@0
|
74 get(D, member, namespace, NSI),
|
Chris@0
|
75 get(NSI, selection, NSId),
|
Chris@0
|
76 rdf_db:ns(NSId, NS),
|
Chris@0
|
77 get(D, member, id, IDI),
|
Chris@0
|
78 get(IDI, selection, Label),
|
Chris@0
|
79 uri_from_label(NS, Label, Resource),
|
Chris@0
|
80 rdfe_transaction(send(D, do_create_resource, Resource, Label),
|
Chris@0
|
81 create_resource),
|
Chris@0
|
82 send(IDI, clear),
|
Chris@0
|
83 ( get(D, client, Client),
|
Chris@0
|
84 send(Client, has_send_method, resource_created)
|
Chris@0
|
85 -> get(D, role, Role),
|
Chris@0
|
86 send(Client, resource_created, Resource, Role)
|
Chris@0
|
87 ; true
|
Chris@0
|
88 ).
|
Chris@0
|
89
|
Chris@0
|
90 do_create_resource(D, Resource:name, Label:name) :->
|
Chris@0
|
91 "Create a new resource"::
|
Chris@0
|
92 get(D, resource, Super),
|
Chris@0
|
93 ( get(D, member, file, FileItem),
|
Chris@0
|
94 get(FileItem, selection, File)
|
Chris@0
|
95 -> true
|
Chris@0
|
96 ; File = user
|
Chris@0
|
97 ),
|
Chris@0
|
98 ( get(D, role, rdf_class_node) % TBD: generalise!
|
Chris@0
|
99 -> ( ( rdf_has(Super, rdf:type, MetaClass, Type)
|
Chris@0
|
100 *-> rdfe_assert(Resource, Type, MetaClass, File)
|
Chris@0
|
101 ; rdfe_assert(Resource, rdf:type, rdfs:'Class', File)
|
Chris@0
|
102 ),
|
Chris@0
|
103 fail
|
Chris@0
|
104 ; true
|
Chris@0
|
105 ),
|
Chris@0
|
106 rdfe_assert(Resource, rdfs:subClassOf, Super, File)
|
Chris@0
|
107 ; rdfe_assert(Resource, rdf:type, Super, File)
|
Chris@0
|
108 ),
|
Chris@0
|
109 ( Label \== Resource
|
Chris@0
|
110 -> rdfe_assert(Resource, rdfs:label, literal(Label), File)
|
Chris@0
|
111 ; true
|
Chris@0
|
112 ).
|
Chris@0
|
113
|
Chris@0
|
114 % uri_from_label(+NS, +Typed, -URI)
|
Chris@0
|
115 %
|
Chris@0
|
116 % Deduce the URI from the entered namespace and identifier field.
|
Chris@0
|
117 % If the typed identifier is already an absolute URI we simply
|
Chris@0
|
118 % use that.
|
Chris@0
|
119
|
Chris@0
|
120 uri_from_label(_, URI, URI) :-
|
Chris@0
|
121 is_absolute_url(URI), !.
|
Chris@0
|
122 uri_from_label(NS, Label, URI) :-
|
Chris@0
|
123 new(S, string('%s', Label)),
|
Chris@0
|
124 send(S, translate, ' ', '_'),
|
Chris@0
|
125 send(S, prepend, NS),
|
Chris@0
|
126 get(S, value, URI),
|
Chris@0
|
127 free(S).
|
Chris@0
|
128
|
Chris@0
|
129 :- pce_end_class(rdf_create_dialog).
|
Chris@0
|
130
|
Chris@0
|
131
|
Chris@0
|
132 :- pce_begin_class(rdf_ns_menu, menu,
|
Chris@0
|
133 "Prompt for namespace").
|
Chris@0
|
134
|
Chris@0
|
135 initialise(M, Default:[name], Msg:[code]*) :->
|
Chris@0
|
136 "Create from Default (short id)"::
|
Chris@0
|
137 send_super(M, initialise, namespace, cycle, Msg),
|
Chris@0
|
138 findall(NS, rdf_db:ns(NS, _), List0),
|
Chris@0
|
139 sort(List0, List),
|
Chris@0
|
140 ( member(NS, List),
|
Chris@0
|
141 send(M, append, menu_item(NS, @default, NS)),
|
Chris@0
|
142 fail
|
Chris@0
|
143 ; true
|
Chris@0
|
144 ),
|
Chris@0
|
145 ( Default \== @default,
|
Chris@0
|
146 get(M, member, Default, MI)
|
Chris@0
|
147 -> send(M, selection, MI)
|
Chris@0
|
148 ; true
|
Chris@0
|
149 ),
|
Chris@0
|
150 send(M, show_label, @off).
|
Chris@0
|
151
|
Chris@0
|
152 :- pce_end_class(rdf_ns_menu).
|
Chris@0
|
153
|
Chris@0
|
154 :- pce_begin_class(rdf_file_menu, menu,
|
Chris@0
|
155 "Prompt for file").
|
Chris@0
|
156
|
Chris@0
|
157 initialise(M, Default:[name], Msg:[code]*) :->
|
Chris@0
|
158 send_super(M, initialise, file, cycle, Msg),
|
Chris@0
|
159 findall(File, rdf_source(File), List0),
|
Chris@0
|
160 sort(List0, List),
|
Chris@0
|
161 ( member(File, List),
|
Chris@0
|
162 file_base_name(File, Base),
|
Chris@0
|
163 send(M, append, menu_item(File, @default, Base)),
|
Chris@0
|
164 fail
|
Chris@0
|
165 ; true
|
Chris@0
|
166 ),
|
Chris@0
|
167 ( Default \== @default
|
Chris@0
|
168 -> ( get(M, member, Default, MI)
|
Chris@0
|
169 -> true
|
Chris@0
|
170 ; send(M, append, new(MI, menu_item(Default, @default)))
|
Chris@0
|
171 ),
|
Chris@0
|
172 send(M, selection, MI)
|
Chris@0
|
173 ; true
|
Chris@0
|
174 ).
|
Chris@0
|
175
|
Chris@0
|
176 :- pce_end_class(rdf_file_menu).
|
Chris@0
|
177
|
Chris@0
|
178 :- pce_begin_class(rdf_id_item, identifier_item,
|
Chris@0
|
179 "Enter a local id").
|
Chris@0
|
180
|
Chris@0
|
181 initialise(ID, Default:[name]) :->
|
Chris@0
|
182 send_super(ID, initialise, id, Default),
|
Chris@0
|
183 send(ID, show_label, @off).
|
Chris@0
|
184
|
Chris@0
|
185 typed(Id, Ev:event) :->
|
Chris@0
|
186 ( get(Ev, id, 27)
|
Chris@0
|
187 -> send(Id?device, cancel) % hack!
|
Chris@0
|
188 ; send_super(Id, typed, Ev)
|
Chris@0
|
189 ).
|
Chris@0
|
190
|
Chris@0
|
191 :- pce_end_class(rdf_id_item).
|
Chris@0
|
192
|
Chris@0
|
193
|
Chris@0
|
194 /*******************************
|
Chris@0
|
195 * PROPERTY ON CLASS *
|
Chris@0
|
196 *******************************/
|
Chris@0
|
197
|
Chris@0
|
198 :- pce_begin_class(rdf_property_on_class_dialog, rdf_dialog,
|
Chris@0
|
199 "Create a property for a class").
|
Chris@0
|
200
|
Chris@0
|
201 variable(resource, name, get, "Class to make a property for").
|
Chris@0
|
202
|
Chris@0
|
203 initialise(D, Class:name, For:[graphical]) :->
|
Chris@0
|
204 send(D, slot, resource, Class),
|
Chris@0
|
205 call_rules(D, label_text(Class, Label)),
|
Chris@0
|
206 send_super(D, initialise, For,
|
Chris@0
|
207 string('Define property for %s', Label)),
|
Chris@0
|
208 rdf_default_file(Class, File, NS),
|
Chris@0
|
209 send(D, append, new(rdf_file_menu(File))),
|
Chris@0
|
210 send(D, append, new(rdf_ns_menu(NS))), % TBD: update if file changes
|
Chris@0
|
211 send(D, append, new(ID, rdf_id_item), right),
|
Chris@0
|
212 send(ID, alignment, left),
|
Chris@0
|
213 send(D, add_select_item, type, rdf:type, rdf:'Property'),
|
Chris@0
|
214 send(D, add_select_item, range, rdf:range, rdfs:'Resource'),
|
Chris@0
|
215
|
Chris@0
|
216 send(D, append, new(C, button(create, message(D, create_resource)))),
|
Chris@0
|
217 send(D, append, button(cancel)),
|
Chris@0
|
218 send(C, default_button, @on).
|
Chris@0
|
219
|
Chris@0
|
220 add_select_item(D, Name:name, Prop:prolog, Root:prolog) :->
|
Chris@0
|
221 rdf_global_id(Prop, PropRes),
|
Chris@0
|
222 rdf_global_id(Root, RootRes),
|
Chris@0
|
223 send(D, append, new(I, rdfs_resource_item(PropRes, RootRes, @nil,
|
Chris@0
|
224 class(RootRes)))),
|
Chris@0
|
225 send(I, name, Name).
|
Chris@0
|
226
|
Chris@0
|
227 create_resource(D) :->
|
Chris@0
|
228 rdfe_transaction(send(D, do_create_resource), create_property).
|
Chris@0
|
229
|
Chris@0
|
230 do_create_resource(D) :->
|
Chris@0
|
231 get(D, resource, Domain),
|
Chris@0
|
232 get(D, item_selection, namespace, NSId),
|
Chris@0
|
233 get(D, item_selection, id, Label),
|
Chris@0
|
234 get(D, item_selection, type, Type),
|
Chris@0
|
235 get(D, item_selection, range, Range),
|
Chris@0
|
236 get(D, item_selection, file, File),
|
Chris@0
|
237 rdf_db:ns(NSId, NS),
|
Chris@0
|
238 uri_from_label(NS, Label, Resource),
|
Chris@0
|
239
|
Chris@0
|
240 rdfe_assert(Resource, rdf:type, Type, File),
|
Chris@0
|
241 rdfe_assert(Resource, rdfs:label, literal(Label), File),
|
Chris@0
|
242 rdfe_assert(Resource, rdfs:domain, Domain, File),
|
Chris@0
|
243 rdfe_assert(Resource, rdfs:range, Range, File),
|
Chris@0
|
244
|
Chris@0
|
245 send(D, destroy).
|
Chris@0
|
246
|
Chris@0
|
247
|
Chris@0
|
248 :- pce_end_class(rdf_property_on_class_dialog).
|