1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Bousi-Prolog documentation generator
    3
    4:- module(builddoc, [
    5		create_documentation/1  % +LatexFile
    6   ]).    7
    8:- use_module(library(doc_latex)).    9
   10%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   11
   12
   13
   14%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   15% Main predicate for building Bousi-Prolog documentation
   16%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 create_documentation(+LatexFile)
Initial predicate of the Bousi-Prolog documentation generator. This predicate loads both the Bousi-Prolog system and the test launcher into memory and writes the documentation of all their modules (including this one) to a LaTeX file called LatexFile.
   27create_documentation(LatexFile) :-
   28	consult('../source/bousi'),
   29	consult('../test/test'),
   30	source_files(Filenames),
   31	doc_latex(Filenames, LatexFile, [stand_alone(true), public_only(false)]).
   32
   33
   34
   35%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   36% Constant predicates
   37%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 source_files(?Filenames)
Returns a list with the paths of the Prolog source code files that make up the Bousi-Prolog system, the documentation generator and the test launcher.
   47source_files([
   48              % Bousi-Prolog system
   49              '../source/bousi', '../source/bplHelp.pl',
   50              '../source/directives.pl', '../source/evaluator.pl',
   51              '../source/flags.pl', '../source/foreign.pl',
   52              '../source/parser.pl', '../source/translator.pl',
   53              '../source/utilities.pl',
   54              % Documentation generator
   55              'builddoc.pl',
   56              % Test launcher
   57              '../test/test.pl', '../test/test_prolog.pl',
   58              '../test/test_bousiprolog.pl', '../test/test_errors.pl',
   59              '../test/test_shell.pl'
   60             ])