1/* Part of SWISH 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2015-2017, VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(swish_include, 36 [ include/2 % +File, +Options 37 ]). 38:- use_module(storage). 39:- use_module(config). 40:- use_module(library(sandbox), []). 41:- use_module(library(debug)). 42:- use_module(library(option)). 43:- use_module(library(filesex)). 44:- use_module(library(error)). 45:- use_module(library(readutil)).
:- include(Version).
,
but more explicit.If the same file is included at two places it is included at most once. Additionally
The envisioned model is that we can specify which version is, possibly indirectly, included by using directives like this:
:- include(File, [version(Hash)]).
87include(File, Version) :- 88 throw(error(context_error(nodirective, include(File, Version)), _)). 89 90swishterm_expansion(:- include(FileIn), Expansion) :- 91 swish:term_expansion(:- include(FileIn, []), Expansion). 92swishterm_expansion(:- include(FileIn, Options), Expansion) :- 93 setup_call_cleanup( 94 '$push_input_context'(swish_include), 95 expand_include(FileIn, Options, Expansion), 96 '$pop_input_context'). 97 98expand_include(FileIn, Options, Expansion) :- 99 include_file_id(FileIn, File, Options), 100 arg(2, File, IncludeID), 101 ( prolog_load_context(module, Module), 102 clause(Module:'swish included'(IncludeID), true) 103 -> Expansion = [] 104 ; Expansion = [ (:- discontiguous('swish included'/1)), 105 'swish included'(IncludeID), 106 (:- include(stream(URI, Stream, [close(true)]))) 107 ], 108 include_data(File, URI, Data), 109 open_string(Data, Stream) 110 ).
116include_data(file(Name, _Data, gitty(Meta)), URI, Data) :- 117 !, 118 catch(storage_file(Meta.commit, Data, _Meta), 119 error(existence_error(_,_),_), 120 fail), 121 atom_concat('swish://', Name, URI). 122include_data(file(Spec, Spec, filesystem), URI, Data) :- 123 absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]), 124 read_file_to_string(Path, Data, []), 125 Spec =.. [Alias,_], 126 file_base_name(Path, NameExt), 127 format(atom(URI), 'swish://~w/~w', [Alias, NameExt]).
134include_file_id(FileIn, file(File, IncludeID, gitty(Meta)), Options) :- 135 atomic(FileIn), 136 !, 137 atom_string(File0, FileIn), 138 add_extension(File0, File), 139 ( option(version(Version), Options) 140 -> storage_meta_data(Version, Meta) 141 ; storage_meta_data(File, Meta) 142 ), 143 atom_concat('swish://', Meta.name, URI), 144 IncludeID0 = gitty(Meta.commit, Meta.data, URI), 145 ( prolog_load_context(module, Module), 146 clause(Module:'swish included'(IncludeIDPrev), true), 147 compatible_versions(IncludeIDPrev, IncludeID0, Version) 148 -> IncludeID = IncludeIDPrev 149 ; IncludeID = IncludeID0 150 ). 151include_file_id(FileIn, file(File, File, filesystem), _) :- 152 compound(FileIn), 153 FileIn =.. [Alias,NameIn], 154 atom_string(Name, NameIn), 155 ( safe_name(Name), 156 swish_config(include_alias, Alias) 157 -> true 158 ; permission_error(include, file, Name) 159 ), 160 File =.. [Alias,Name]. 161 162compatible_versions(Version, Version, _) :- !. 163compatible_versions(gitty(_, DataHash, _), gitty(_, DataHash, _), _) :- !. 164compatible_versions(Gitty1, Gitty2, Version) :- !, 165 Gitty1 = gitty(_, _, URI), 166 Gitty2 = gitty(_, _, URI), 167 ( var(Version) 168 -> true 169 ; throw(error(version_error(Gitty1, Gitty2), _)) 170 ). 171 172safe_name(Name) :- 173 \+ ( sub_atom(Name, 0, _, _, '../') 174 ; sub_atom(Name, _, _, _, '/../') 175 ; sub_atom(Name, _, _, 0, '/..') 176 ; Name == '..' 177 ).
184file_alias(File, Spec) :-
185 atomic_list_concat([Alias,Name], /, File),
186 swish_config(include_alias, Alias),
187 safe_name(Name),
188 !,
189 Spec =.. [Alias,Name].
195add_extension(File, FileExt) :- 196 file_name_extension(_, Ext, File), 197 Ext \== '', 198 !, 199 FileExt = File. 200add_extension(Hash, Hash) :- 201 is_hash(Hash), 202 !. 203add_extension(File, FileExt) :- 204 file_name_extension(File, pl, FileExt). 205 206is_hash(Name) :- 207 atom_length(Name, 40), 208 split_string(Name, ":", "0123456789abcdef", [""]). 209 210 211 /******************************* 212 * SANDBOX * 213 *******************************/ 214 215:- multifile 216 sandbox:safe_directive/1. 217 218sandbox:safe_directive(M:include(stream(Id, Stream, [close(true)]))) :- 219 is_stream(Stream), 220 sub_atom(Id, 0, _, _, 'swish://'), 221 prolog_load_context(module, M). 222 223 224 /******************************* 225 * COLOUR * 226 *******************************/ 227 228:- multifile 229 prolog_colour:term_colours/2. 230 231prolog_colourterm_colours((:- include(FileIn, Options)), 232 neck(directive) - 233 [ goal(built_in,include(FileIn)) - 234 [ FileClass, 235 classify 236 ] 237 ]) :- 238 classify_include(FileIn, FileClass, Options). 239prolog_colourterm_colours((:- include(FileIn)), 240 neck(directive) - 241 [ goal(built_in,include(FileIn)) - 242 [ FileClass 243 ] 244 ]) :- 245 classify_include(FileIn, FileClass, []). 246 247classify_include(FileIn, FileClass, Options) :- 248 debug(include, 'Classifying ~p', [FileIn]), 249 ( catch(include_file_id(FileIn, FileID, Options), _, fail) 250 -> classify_include(FileID, FileClass) 251 ; FileClass = nofile 252 ), 253 debug(include, 'Class ~p', [FileClass]). 254 255classify_include(file(Name, _DataHash, gitty(Meta)), FileClass) :- 256 !, 257 ( is_hash(Name) 258 -> format(atom(Id), 'swish://~w@~w', [Meta.name, Name]) 259 ; atom_concat('swish://', Name, Id) 260 ), 261 FileClass = file(Id). 262classify_include(file(Spec, Spec, filesystem), FileClass) :- 263 absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]), 264 Spec =.. [Alias,_], 265 file_base_name(Path, NameExt), 266 format(atom(URI), 'swish://~w/~w', [Alias, NameExt]), 267 FileClass = file(URI). 268 269 270 /******************************* 271 * XREF * 272 *******************************/ 273 274:- multifile 275 prolog:xref_open_source/2, 276 prolog:xref_source_file/3, 277 prolog:xref_source_identifier/2, 278 prolog:xref_source_time/2.
286prologxref_source_identifier(Src, Id) :- 287 atom(Src), 288 sub_atom(Src, 0, _, _, 'swish://'), 289 !, 290 Id = Src. 291 292prologxref_open_source(File, Stream) :- 293 atom(File), 294 atom_concat('swish://', Name, File), 295 ( file_alias(File, Spec) 296 -> absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]), 297 open(Path, read, Stream) 298 ; catch(storage_file(Name, Data, _Meta), _, fail), 299 open_string(Data, Stream) 300 ). 301 302prologxref_source_time(File, Modified) :- 303 atom(File), 304 atom_concat('swish://', Name, File), 305 ( file_alias(File, Spec) 306 -> absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]), 307 time_file(Path, Modified) 308 ; catch(storage_meta_data(Name, Meta), _, fail), 309 Modified = Meta.get(time) 310 ).
include(program)
to support
the cross-referencer.317prologxref_source_file(stream(Id, _Stream, [close(true)]), Id, _). 318prologxref_source_file(File, Id, Options) :- 319 atom(File), 320 option(relative_to(Src), Options), 321 atom(Src), 322 atom_concat('swish://', SrcFile, Src), 323 add_extension(File, FileExt), 324 file_directory_name(SrcFile, SrcDir), 325 directory_file_path(SrcDir, FileExt, TargetFile), 326 atom_concat('swish://', TargetFile, Id)
Support :-
include(File)
from SWISHThis module allows SWISH programs to include other programs from the shared gitty store. It realises this using the following steps:
We allow for hierarchical and circular includes. */