1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2006-2012, University of Amsterdam 7 VU University Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(pldoc_files, 37 [ doc_save/2, % +File, +Options 38 doc_pack/1 % +Pack (re-export from doc_pack) 39 ]). 40:- use_module(library(pldoc), []). 41:- use_module(pldoc(doc_html)). 42:- use_module(pldoc(doc_index)). 43:- use_module(pldoc(doc_pack)). 44:- use_module(library(option)). 45:- use_module(library(lists)). 46:- use_module(library(filesex)).
59:- predicate_options(doc_save/2, 2,
60 [ format(oneof([html])),
61 doc_root(atom),
62 man_server(atom),
63 index_file(atom),
64 if(oneof([loaded,true])),
65 recursive(boolean),
66 css(oneof([copy,inline])),
67 title(atom)
68 ]).
file(s)
. Options include
html
.doc
.http://www.swi-prolog.org/pldoc/
index
.loaded
(default)
only documents files loaded into the Prolog image. true
documents all files.true
, recurse into subdirectories.copy
, copy the CSS file to created directories.
Using inline
, include the CSS file into the created
files. Currently, only the default copy
is supported.
The typical use-case is to document the Prolog files that belong
to a project in the current directory. To do this load the
Prolog files and run the goal below. This creates a
sub-directory doc
with an index file index.html
. It
replicates the directory structure of the source directory,
creating an HTML file for each Prolog file and an index file for
each sub-directory. A copy of the required CSS and image
resources is copied to the doc
directory.
?- doc_save(., [recursive(true)]).
122doc_save(Spec, Options) :-
123 doc_target(Spec, Target, Options),
124 target_directory(Target, Dir),
125 phrase(file_map(Target), FileMap),
126 merge_options([ html_resources(pldoc_files),
127 source_link(false),
128 resource_directory(Dir)
129 ], Options, Options1),
130 Options2 = [files(FileMap)|Options1],
131 setup_call_cleanup(
132 nb_setval(pldoc_options, Options2),
133 generate(Target, Options2),
134 nb_delete(pldoc_options)),
135 copy_resources(Dir, Options2).
143generate([], _). 144generate([H|T], Options) :- 145 \+ \+ generate(H, Options), 146 generate(T, Options). 147generate(file(PlFile, DocFile), Options) :- 148 b_setval(pldoc_output, DocFile), 149 setup_call_cleanup( 150 open(DocFile, write, Out, [encoding(utf8)]), 151 with_output_to(Out, doc_for_file(PlFile, Options)), 152 close(Out)). 153generate(directory(Dir, IndexFile, Members, DirOptions), Options) :- 154 append(DirOptions, Options, AllOptions), 155 b_setval(pldoc_output, IndexFile), 156 setup_call_cleanup( 157 open(IndexFile, write, Out, [encoding(utf8)]), 158 with_output_to( 159 Out, 160 doc_for_dir(Dir, 161 [ members(Members) 162 | AllOptions 163 ])), 164 close(Out)), 165 generate(Members, Options).
180doc_target(FileOrDir, file(File, DocFile), Options) :- 181 absolute_file_name(FileOrDir, File, 182 [ file_type(prolog), 183 file_errors(fail), 184 access(read) 185 ]), 186 !, 187 ( option(source_root(_), Options) 188 -> Options1 = Options 189 ; file_directory_name(File, FileDir), 190 Options1 = [source_root(FileDir)|Options] 191 ), 192 document_file(File, DocFile, Options1). 193doc_target(FileOrDir, directory(Dir, Index, Members, DirOptions), Options0) :- 194 absolute_file_name(FileOrDir, Dir, 195 [ file_type(directory), 196 file_errors(fail), 197 access(read) 198 ]), 199 !, 200 ( option(source_root(_), Options0) % recursive 201 -> Options = Options0 202 ; Options1 = [source_root(Dir)|Options0], % top 203 exclude(main_option, Options1, Options2), 204 set_doc_root(Dir, Options2, Options) 205 ), 206 DirOptions = Options, 207 document_file(Dir, Index, Options), 208 findall(Member, 209 ( prolog_file_in_dir(Dir, File, Options), 210 doc_target(File, Member, Options) 211 ), 212 Members).
218main_option(title(_)). 219main_option(readme(_)). 220main_option(todo(_)). 221 222target_directory(directory(_, Index, _, _), Dir) :- 223 file_directory_name(Index, Dir). 224target_directory(file(_, DocFile), Dir) :- 225 file_directory_name(DocFile, Dir). 226 227set_doc_root(_Dir, Options0, Options) :- 228 option(doc_root(_), Options0), 229 !, 230 Options = Options0. 231set_doc_root(Dir, Options0, Options) :- 232 directory_file_path(Dir, doc, DocRoot), 233 Options = [doc_root(DocRoot)|Options0].
file(PlFile, DocFile)
for files that need to
be documented.240file_map([]) --> 241 []. 242file_map([H|T]) --> 243 file_map(H), 244 file_map(T). 245file_map(file(Src, Doc)) --> 246 [ file(Src, Doc) ]. 247file_map(directory(_Dir, _Doc, Members, _Options)) --> 248 file_map(Members).
257document_file(File, DocFile, Options) :-
258 ( option(if(loaded), Options, loaded)
259 -> ( source_file(File)
260 -> true
261 ; exists_directory(File),
262 source_file(SrcFile),
263 sub_atom(SrcFile, 0, _, _, File)
264 -> true
265 )
266 ; true
267 ),
268 option(format(Format), Options, html),
269 doc_extension(Format, Ext),
270 ( exists_directory(File)
271 -> option(index_file(Index), Options, index),
272 atomic_list_concat([File, /, Index, '.', Ext], DocFile0)
273 ; file_name_extension(Base, _, File),
274 file_name_extension(Base, Ext, DocFile0)
275 ),
276 ( option(doc_root(Dir0), Options),
277 ensure_slash(Dir0, Dir)
278 -> ( option(source_root(SrcTop), Options)
279 -> true
280 ; working_directory(SrcTop, SrcTop)
281 ),
282 directory_file_path(SrcTop, Local, DocFile0),
283 directory_file_path(Dir, Local, DocFile),
284 file_directory_name(DocFile, DocDir),
285 ensure_dir(DocDir, Options)
286 ; DocFile = DocFile0
287 ).
292doc_extension(html, html). 293doc_extension(latex, tex).
300ensure_slash(DirName, WithSlash) :-
301 ( sub_atom(DirName, _, _, 0, /)
302 -> WithSlash = DirName
303 ; atom_concat(DirName, /, WithSlash)
304 ).
311ensure_dir(Directory, _Options) :- 312 exists_directory(Directory), 313 !. 314ensure_dir(Directory, Options) :- 315 file_directory_name(Directory, Parent), 316 Parent \== Directory, 317 ensure_dir(Parent, Options), 318 make_directory(Directory).
true
, also generate subdirectories328prolog_file_in_dir(Dir, File, Options) :- 329 ( option(if(loaded), Options, loaded) 330 -> source_file(File), 331 file_directory_name(File, Dir) 332 ; user:prolog_file_type(Ext, prolog), 333 \+ user:prolog_file_type(Ext, qlf), 334 atomic_list_concat([Dir, '/*.', Ext], Pattern), 335 expand_file_name(Pattern, Files), 336 member(File, Files) 337 ), 338 file_base_name(File, Base), 339 \+ blocked(Base). 340prolog_file_in_dir(Dir, SubDir, Options) :- 341 option(recursive(true), Options, false), 342 option(doc_root(DocRoot), Options), 343 atom_concat(Dir, '/*', Pattern), 344 expand_file_name(Pattern, Matches), 345 member(SubDir, Matches), 346 SubDir \== DocRoot, 347 exists_directory(SubDir).
353blocked('.plrc'). 354blocked('INDEX.pl'). 355 356 357 /******************************* 358 * RESOURCES * 359 *******************************/
363copy_resources(Dir, Options) :- 364 option(format(Format), Options, html), 365 forall(doc_resource(Format, Res), 366 ( absolute_file_name(pldoc(Res), File, [access(read)]), 367 copy_file(File, Dir))). 368 369doc_resource(html, 'pldoc.css'). 370doc_resource(html, 'h1-bg.png'). 371doc_resource(html, 'h2-bg.png'). 372doc_resource(html, 'multi-bg.png'). 373doc_resource(html, 'priv-bg.png'). 374doc_resource(html, 'pub-bg.png')
Create stand-alone documentation files
Create stand-alone documentation from a bundle of source-files. Typical use of the PlDoc package is to run it as a web-server from the project in progress, providing search and guaranteed consistency with the loaded version. Creating stand-alone files as provided by this file can be useful for printing or distribution.