1\chapter{Modules}                 \label{sec:modules}
2
3A Prolog module is a collection of predicates which defines a public
4interface by means of a set of provided predicates and operators. Prolog
5modules are defined by an ISO standard. Unfortunately, the standard is
6considered a failure and, as far as we are aware, not implemented by any
7concrete Prolog implementation. The SWI-Prolog module system syntax is
8derived from the Quintus Prolog module system. The Quintus module system
9has been the starting point for the module systems of a number of
10mainstream Prolog systems, such as SICStus, Ciao and YAP. The underlying
11primitives of the SWI-Prolog module system differ from the mentioned
12systems. These primitives allow for multiple modules in a file,
13hierarchical modules, emulation of other modules interfaces, etc.
14
15This chapter motivates and describes the SWI-Prolog module system.
16Novices can start using the module system after reading
17\secref{defmodule} and \secref{import}. The primitives defined in these
18sections suffice for basic usage until one needs to export predicates
19that call or manage other predicates dynamically (e.g., use call/1,
20assert/1, etc.). Such predicates are called \jargon{meta predicates} and
21are discussed in \secref{metapred}. \Secref{overrule} to \secref{moduleop}
22describe more advanced issues. Starting with \secref{importmodule}, we
23discuss more low-level aspects of the SWI-Prolog module system that
24are used to implement the visible module system, and can be used to
25build other code reuse mechanisms.
26
27
28\section{Why Use Modules?}		\label{sec:whymodules}
29
30In classic Prolog systems, all predicates are organised in a single
31namespace and any predicate can call any predicate. Because each
32predicate in a file can be called from anywhere in the program, it
33becomes very hard to find the dependencies and enhance the
34implementation of a predicate without risking to break the overall
35application.  This is true for any language, but even worse for
36Prolog due to its frequent need for `helper predicates'.
37
38A Prolog module encapsulates a set of predicates and defines an
39\jargon{interface}. Modules can import other modules, which makes the
40dependencies explicit. Given explicit dependencies and a well-defined
41interface, it becomes much easier to change the internal organisation of
42a module without breaking the overall application.
43
44Explicit dependencies can also be used by the development environment.
45The SWI-Prolog library \pllib{prolog_xref} can be used to analyse
46completeness and consistency of modules. This library is used by the
47built-in editor PceEmacs for syntax highlighting, jump-to-definition,
48etc.
49
50
51\section{Defining a Module}		\label{sec:defmodule}
52
53Modules are normally created by loading a \jargon{module file}. A module
54file is a file holding a module/2 directive as its first term. The
55module/2 directive declares the name and the public (i.e., externally
56visible) predicates of the module. The rest of the file is loaded into
57the module. Below is an example of a module file, defining reverse/2 and
58hiding the helper predicate rev/3. A module can use all built-in
59predicates and, by default, cannot redefine system predicates.
60
61\begin{code}
62:- module(reverse, [reverse/2]).
63
64reverse(List1, List2) :-
65        rev(List1, [], List2).
66
67rev([], List, List).
68rev([Head|List1], List2, List3) :-
69        rev(List1, [Head|List2], List3).
70\end{code}
71
72The module is named \const{reverse}. Typically, the name of a module is
73the same as the name of the file by which it is defined without the
74filename extension, but this naming is not enforced. Modules are
75organised in a single and flat namespace and therefore module names must
76be chosen with some care to avoid conflicts. As we will see, typical
77applications of the module system rarely use the name of a module
78explicitly in the source text.
79
80\begin{description}
81    \directive{module}{2}{+Module, +PublicList}
82This directive can only be used as the first term of a source file. It
83declares the file to be a \jargon{module file}, defining a module named
84\arg{Module}. Note that a module name is an atom. The module exports the
85predicates of \arg{PublicList}. \arg{PublicList} is a list of predicate
86indicators (name/arity or name//arity pairs) or operator declarations
87using the format \term{op}{Precedence, Type, Name}. Operators defined in
88the export list are available inside the module as well as to modules
89importing this module. See also \secref{operators}.
90
91Compatible to Ciao Prolog, if \arg{Module} is unbound, it is unified
92with the basename without extension of the file being loaded.
93
94    \directive{module}{3}{+Module, +PublicList, +Dialect}
95Same as module/2.  The additional \arg{Dialect} argument provides a list
96of \jargon{language options}.  Each atom in the list \arg{Dialect} is
97mapped to a use_module/1 goal as given below. See also \secref{dialect}.
98The third argument is supported for compatibility with the
99\href{http://prolog-commons.org/}{Prolog Commons project}.
100
101\begin{code}
102:- use_module(library(dialect/LangOption)).
103\end{code}
104\end{description}
105
106
107\section{Importing Predicates into a Module}	\label{sec:import}
108
109Predicates can be added to a module by \jargon{importing} them from
110another module. Importing adds predicates to the namespace of a
111module. An imported predicate can be called exactly the same as a
112locally defined predicate, although its implementation remains part of
113the module in which it has been defined.
114
115Importing the predicates from another module is achieved using the
116directives use_module/1 or use_module/2. Note that both directives take
117\arg{filename(s)} as arguments. That is, modules are imported based on
118their filename rather than their module name.
119
120\begin{description}
121    \predicate{use_module}{1}{+Files}
122Load the file(s) specified with \arg{Files} just like ensure_loaded/1.
123The files must all be module files. All exported predicates from the
124loaded files are imported into the module from which this predicate is
125called. This predicate is equivalent to ensure_loaded/1, except that it
126raises an error if \arg{Files} are not module files.
127
128The imported predicates act as \jargon{weak symbols} in the module into
129which they are imported. This implies that a local definition of a
130predicate overrides (clobbers) the imported definition. If the flag
131\prologflag{warn_override_implicit_import} is \const{true} (default), a
132warning is printed. Below is an example of a module that uses
133library(lists), but redefines flatten/2, giving it a totally different
134meaning:
135
136\begin{code}
137:- module(shapes, []).
138:- use_module(library(lists)).
139
140flatten(cube, square).
141flatten(ball, circle).
142\end{code}
143
144\noindent
145Loading the above file prints the following message:
146
147\begin{code}
148Warning: /home/janw/Bugs/Import/t.pl:5:
149	Local definition of shapes:flatten/2
150	overrides weak import from lists
151\end{code}
152
153This warning can be avoided by (1) using use_module/2 to only import the
154predicates from the \const{lists} library that are actually used in the `shapes' module, (2)
155using the \exam{except([flatten/2])} option of use_module/2, (3) use
156\exam{:- abolish(flatten/2).} before the local definition or (4) setting
157\prologflag{warn_override_implicit_import} to \const{false}. Globally
158disabling this warning is only recommended if overriding imported
159predicates is common as a result of design choices or the program is
160ported from a system that silently overrides imported predicates.
161
162Note that it is always an error to import two modules with use_module/1
163that export the same predicate.  Such conflicts must be resolved with
164use_module/2 as described above.
165
166    \predicate{use_module}{2}{+File, +ImportList}
167Load \arg{File}, which must be a module file, and import the predicates
168as specified by \arg{ImportList}. \arg{ImportList} is a list of
169predicate indicators specifying the predicates that will be imported
170from the loaded module. \arg{ImportList} also allows for renaming or
171import-everything-except. See also the \const{import} option of
172load_files/2. The first example below loads member/2 from the \const{lists}
173library and append/2 under the name \const{list_concat}, which is how this
174predicate is named in YAP. The second example loads all exports from
175library \const{option} except for meta_options/3. These renaming facilities are
176generally used to deal with portability issues with as few changes as possible
177to the actual code. See also \secref{dialect} and
178\secref{reexport}.
179
180\begin{code}
181:- use_module(library(lists), [ member/2,
182				append/2 as list_concat
183			      ]).
184:- use_module(library(option), except([meta_options/3])).
185\end{code}
186\end{description}
187
188In most cases a module is imported because some of its predicates are
189being used.  However, sometimes a module is imported for other
190reasons, e.g., for its declarations.  In such cases it is best
191practice to use use_module/2 with empty ImportList.  This
192distinguishes an imported module that is used, although not for its
193predicates, from a module that is needlessly imported.
194
195The module/2, use_module/1 and use_module/2 directives are sufficient to
196partition a simple Prolog program into modules. The SWI-Prolog graphical
197cross-referencing tool gxref/0 can be used to analyse the dependencies
198between non-module files and propose module declarations for each file.
199
200\section{Controlled autoloading for modules}	\label{sec:module-autoload}
201
202SWI-Prolog by default support \jargon{autoloading} from its standard
203library. Autoloading implies that when a predicate is found missing
204during execution the library is searched and the predicate is imported
205lazily using use_module/2.  See \secref{autoload} for details.
206
207The advantage of autoloading is that it requires less typing while it
208reduces the startup time and reduces the memory footprint of an
209application. It also allows moving old predicates or emulation thereof
210the the module \pllib{backcomp} without affecting existing code. This
211procedure keeps the libraries and system clean. We make sure that there
212are not two modules that provide the same predicate as autoload
213predicate.
214
215Nevertheless, a disadvantage of this autoloader is that the dependencies
216of a module on the libraries are not explicit and tooling such as
217PceEmacs or gxref/0 are required to find these dependencies.  Some users
218want explicit control over which library predicates are accessed from
219where, preferably by using use_module/2 which explicitly states which
220predicates are imported from which library.\footnote{Note that built-in
221predicates still add predicates for general use to all name spaces.}
222
223Large applications typically contain source files that are not
224immediately needed and often are not needed at all in many runs of the
225program. This can be solved by creating an application-specific autoload
226library, but with multiple parties providing autoloadable predicates the
227maintenance becomes fragile.  For these two reasons we added autoload/1
228and autoload/2 that behave similar to use_module/1,2, but do not perform
229the actual loading.  The generic autoloader now proceeds as follows if
230a missing predicate is encountered:
231
232\begin{enumerate}
233    \item Check autoload/2 declarations.  If one specifies the predicate,
234	  import it using use_module/2.
235    \item Check autoload/1 declarations.  If the specified file is loaded,
236          check its export list. Otherwise read the module declaration
237	  of the target file to find the exports. If the target
238	  predicate is found, import it using use_module/2.
239    \item Perform autoloading from the library if the \prologflag{autoload}
240          is \const{true}.
241\end{enumerate}
242
243\begin{description}
244    \predicate{autoload}{1}{:File}
245    \nodescription
246    \predicate{autoload}{2}{:File, +Imports}
247Declare that possibly missing predicates in the module in which this
248declaration occurs are to be resolved by using use_module/2 on
249\arg{File} to (possibly) load the file and make the target predicate
250available. The autoload/2 variant is tried before autoload/1. It is not
251allowed for two autoload/2 declarations to provide the same predicate
252and it is not allowed to define a predicate provided in this way
253locally.  See also require/1, which allows specifying predicates for
254autoloading from their default location.
255
256Predicates made available using autoload/2 behave as defined predicates,
257which implies that any operation on them will perform autoloading if
258necessary. Notably predicate_property/2, current_predicate/1 and
259clause/2 are supported.
260
261Currently, neither the existence of \arg{File}, nor whether it actually
262exports the given predicates (autoload/2) is verified when the file is
263loaded. Instead, the declarations are verified when searching for a
264missing predicate.
265
266If the Prolog flag \prologflag{autoload} is set to \const{false}, these
267declarations are interpreted as use_module/1,2.
268\end{description}
269
270
271\section{Defining a meta-predicate}
272\label{sec:metapred}
273
274A meta-predicate is a predicate that calls other predicates dynamically,
275modifies a predicate, or reasons about properties of a predicate. Such
276predicates use either a compound term or a \jargon{predicate indicator}
277to describe the predicate they address, e.g., \exam{assert(name(jan))}
278or \exam{abolish(name/1)}. With modules, this simple schema no longer
279works as each module defines its own mapping from name+arity to
280predicate. This is resolved by wrapping the original description in a
281term <module>:<term>, e.g., \exam{assert(person:name(jan))} or
282\exam{abolish(person:name/1)}.
283
284Of course, when calling assert/1 from inside a module, we expect to assert to
285a predicate local to this module. In other words, we do not wish to
286provide this \functor{:}{2} wrapper by hand. The meta_predicate/1
287directive tells the compiler that certain arguments are terms that will
288be used to look up a predicate and thus need to be wrapped (qualified)
289with <module>:<term>, unless they are already wrapped.
290
291In the example below, we use this to define maplist/3 inside a module.
292The argument `2' in the meta_predicate declaration means that the
293argument is module-sensitive and refers to a predicate with an arity
294that is two more than the term that is passed in. The compiler only
295distinguishes the values 0..9 and \chr{:}, which denote module-sensitive
296arguments, from \chr{+}, \chr{-} and \chr{?}, which denote
297\jargon{modes}. The values 0..9 are used by the
298\jargon{cross-referencer} and syntax highlighting. Note that the
299helper predicate \nopredref{maplist_}{3} does not need to be declared as
300a meta-predicate because the maplist/3 wrapper already ensures that
301\arg{Goal} is qualified as <module>:\arg{Goal}. See the description of
302meta_predicate/1 for details.
303
304\begin{code}
305:- module(maplist, [maplist/3]).
306:- meta_predicate maplist(2, ?, ?).
307
308%%      maplist(:Goal, +List1, ?List2)
309%
310%       True if Goal can successfully be applied to all
311%	successive pairs of elements from List1 and List2.
312
313maplist(Goal, L1, L2) :-
314	maplist_(L1, L2, Goal).
315
316maplist_([], [], _).
317maplist_([H0|T0], [H|T], Goal) :-
318	call(Goal, H0, H),
319	maplist_(T0, T, Goal).
320\end{code}
321
322\begin{description}
323    \prefixop{meta_predicate}{+Head, \ldots}
324Define the predicates referenced by the comma-separated list \arg{Head}
325as \jargon{meta-predicates}. Each argument of each head is a
326\jargon{meta argument specifier}. Defined specifiers are given below.
327Only 0..9, \chr{:} and \chr{^} are interpreted; the mode declarations
328\chr{+}, \chr{-} and \chr{?} are ignored.
329
330    \begin{description}
331        \termitem{0..9}{}
332The argument is a term that is used to reference a predicate
333with $N$ more arguments than the given argument term.  For
334example: \exam{call(0)} or \exam{maplist(1, +)}.
335        \termitem{:}{}
336The argument is module-sensitive, but does not directly refer
337to a predicate.  For example: \exam{consult(:)}.
338        \termitem{-}{}
339The argument is not module-sensitive and unbound on entry.
340        \termitem{?}{}
341The argument is not module-sensitive and the mode is unspecified.
342        \termitem{*}{}
343The argument is not module-sensitive and the mode is unspecified.
344The specification \chr{*} is equivalent to \chr{?}.  It is accepted
345for compatibility reasons.  The predicate predicate_property/2 reports
346arguments declared using \chr{*} with \chr{?}.
347        \termitem{+}{}
348The argument is not module-sensitive and bound (i.e., nonvar)
349on entry.
350        \termitem{^}{}
351This extension is used to denote the possibly \verb$^$-annotated goal of
352setof/3, bagof/3, aggregate/3 and aggregate/4. It is processed similar
353to `0', but leaving the \chr{^}/2 intact.
354	\termitem{//}{}
355The argument is a DCG body.  See phrase/3.
356    \end{description}
357
358Each argument that is module-sensitive (i.e., marked 0..9, \chr{:} or
359\chr{^}) is qualified with the context module of the caller if it is not
360already qualified. The implementation ensures that the argument is
361passed as <module>:<term>, where <module> is an atom denoting the name
362of a module and <term> itself is not a \functor{:}{2} term where the
363first argument is an atom. Below is a simple declaration and a number of
364queries.
365
366\begin{code}
367:- meta_predicate
368	meta(0, +).
369
370meta(Module:Term, _Arg) :-
371	format('Module=~w, Term = ~q~n', [Module, Term]).
372\end{code}
373
374\begin{code}
375?- meta(test, x).
376Module=user, Term = test
377?- meta(m1:test, x).
378Module=m1, Term = test
379?- m2:meta(test, x).
380Module=m2, Term = test
381?- m1:meta(m2:test, x).
382Module=m2, Term = test
383?- meta(m1:m2:test, x).
384Module=m2, Term = test
385?- meta(m1:42:test, x).
386Module=42, Term = test
387\end{code}
388
389The meta_predicate/1 declaration is the portable mechanism for defining
390meta-predicates and replaces the old SWI-Prolog specific mechanism
391provided by the deprecated predicates module_transparent/1,
392context_module/1 and strip_module/3.  See also \secref{modulecompat}.
393\end{description}
394
395
396\section{Overruling Module Boundaries}       \label{sec:overrule}
397
398The module system described so far is sufficient to distribute programs
399over multiple modules. There are, however, cases in which we would like
400to be able to overrule this schema and explicitly call a predicate in
401some module or assert explicitly into some module. Calling in a
402particular module is useful for debugging from the user's top level or
403to access multiple implementations of the same interface that reside in
404multiple modules. Accessing the same interface from multiple modules
405cannot be achieved using importing because importing a predicate with
406the same name and arity from two modules results in a name conflict.
407Asserting in a different module can be used to create models dynamically
408in a new module. See \secref{dynamic-modules}.
409
410Direct addressing of modules is achieved using a \functor{:}{2}
411explicitly in a program and relies on the module qualification mechanism
412described in \secref{metapred}.  Here are a few examples:
413
414\begin{code}
415?- assert(world:done).   % asserts done/0 into module world
416?- world:asserta(done).  % the same
417?- world:done.           % calls done/0 in module world
418\end{code}
419
420Note that the second example is the same due to the Prolog flag
421\prologflag{colon_sets_calling_context}. The system predicate asserta/1
422is called in the module \const{world}, which is possible because system
423predicates are \jargon{visible} in all modules.  At the same time, the
424\jargon{calling context} is set to \const{world}. Because meta arguments
425are qualified with the calling context, the resulting call is the same
426as the first example.
427
428\subsection{Explicit manipulation of the calling context}
429\label{sec:set-calling-context}
430
431Quintus' derived module systems have no means to separate the lookup
432module (for finding predicates) from the calling context (for qualifying
433meta arguments). Some other Prolog implementations (e.g., ECLiPSe and
434IF/Prolog) distinguish these operations, using \functor{@}{2} for
435setting the calling context of a goal. This is provided by SWI-Prolog,
436currently mainly to support compatibility layers.
437
438\begin{description}
439    \predicate{@}{2}{:Goal, +Module}
440Execute \arg{Goal}, setting the calling context to \arg{Module}. Setting
441the calling context affects meta-predicates, for which meta arguments
442are qualified with \arg{Module} and transparent predicates (see
443module_transparent/1).  It has no implications for other predicates.
444
445For example, the code \exam{asserta(done)@world} is the same as
446\exam{asserta(world:done)}.  Unlike in \exam{world:asserta(done)},
447asserta/1 is resolved in the current module rather than the module
448\const{world}.  This makes no difference for system predicates, but
449usually does make a difference for user predicates.
450
451Not that SWI-Prolog does not define \chr{@} as an operator.  Some
452systems define this construct using \exam{op(900, xfx, @)}.
453\end{description}
454
455
456\section{Interacting with modules from the top level}
457\label{sec:mtoplevel}
458
459Debugging often requires interaction with predicates that reside in
460modules: running them, setting spy points on them, etc. This can be
461achieved using the <module>:<term> construct explicitly as described
462above. In SWI-Prolog, you may also wish to omit the module
463qualification. Setting a spy point (spy/1) on a plain predicate sets a
464spy point on any predicate with that name in any module. Editing
465(edit/1) or calling an unqualified predicate invokes the DWIM (Do What I
466Mean) mechanism, which generally suggests the correct qualified query.
467
468Mainly for compatibility, we provide module/1 to switch the module
469with which the interactive top level interacts:
470
471\begin{description}
472    \predicate{module}{1}{+Module}
473The call \exam{module(\arg{Module})} may be used to switch the default
474working module for the interactive top level (see prolog/0).  This may
475be used when debugging a module. The example below lists the clauses
476of file_of_label/2 in the module \const{tex}.
477
478\begin{code}
4791 ?- module(tex).
480true.
481tex: 2 ?- listing(file_of_label/2).
482...
483\end{code}
484\end{description}
485
486
487
488\section{Composing modules from other modules}
489\label{sec:reexport}
490
491The predicates in this section are intended to create new modules from
492the content of other modules. Below is an example to define a
493\emph{composite} module.  The example exports all public predicates
494of \const{module_1}, \const{module_2} and \const{module_3}, pred/1
495from \const{module_4}, all predicates from \const{module_5} except
496do_not_use/1 and all predicates from \const{module_6} while renaming
497pred/1 into mypred/1.
498
499\begin{code}
500:- module(my_composite, []).
501:- reexport([ module_1,
502	      module_2,
503	      module_3
504	    ]).
505:- reexport(module_4, [ pred/1 ]).
506:- reexport(module_5, except([do_not_use/1])).
507:- reexport(module_6, except([pred/1 as mypred])).
508\end{code}
509
510
511\begin{description}
512    \predicate{reexport}{1}{+Files}
513Load and import predicates as use_module/1 and re-export all imported
514predicates. The reexport declarations must immediately follow the module
515declaration.
516
517    \predicate{reexport}{2}{+File, +Import}
518Import from \arg{File} as use_module/2 and re-export the imported
519predicates. The reexport declarations must immediately follow the module
520declaration.
521\end{description}
522
523
524\section{Operators and modules}
525\label{sec:moduleop}
526
527Operators (\secref{operators}) are local to modules, where the initial
528table behaves as if it is copied from the module \const{user} (see
529\secref{resmodules}).  A specific operator can be disabled inside a
530module using \exam{:- op(0, Type, Name)}.  Inheritance from the public
531table can be restored using \exam{:- op(-1, Type, Name)}.
532
533In addition to using the op/3 directive, operators can be declared in
534the module/2 directive as shown below. Such operator declarations are
535visible inside the module, and importing such a module makes the
536operators visible in the target module. Exporting operators is typically
537used by modules that implement sub-languages such as chr (see
538\chapref{chr}). The example below is copied from the library
539\pllib{clpfd}.
540
541\begin{code}
542:- module(clpfd,
543	  [ op(760, yfx, #<==>),
544	    op(750, xfy, #==>),
545	    op(750, yfx, #<==),
546	    op(740, yfx, #\/),
547	    ...
548	    (#<==>)/2,
549	    (#==>)/2,
550	    (#<==)/2,
551	    (#\/)/2,
552	    ...
553	  ]).
554\end{code}
555
556
557\section{Dynamic importing using import modules}
558\label{sec:importmodule}
559
560Until now we discussed the public module interface that is, at least to
561some extent, portable between Prolog implementations with a module system
562that is derived from Quintus Prolog. The remainder of this chapter
563describes the underlying mechanisms that can be used to emulate other
564module systems or implement other code-reuse mechanisms.
565
566In addition to built-in predicates, imported predicates and locally
567defined predicates, SWI-Prolog modules can also call predicates from its
568\jargon{import modules}. Each module has a (possibly empty) list of
569import modules. In the default setup, each new module has a single
570import module, which is \const{user} for all normal user modules and
571\const{system} for all system library modules. Module \const{user}
572imports from \const{system} where all built-in predicates reside. These
573special modules are described in more detail in \secref{resmodules}.
574
575The list of import modules can be manipulated and queried using the
576following predicates, as well as using set_module/1.
577
578\begin{description}
579    \predicate[nondet]{import_module}{2}{+Module, -Import}
580True if \arg{Module} inherits directly from \arg{Import}. All normal
581modules only import from \const{user}, which imports from
582\const{system}. The predicates add_import_module/3 and
583delete_import_module/2 can be used to manipulate the import list.
584See also default_module/2.
585
586    \predicate[multi]{default_module}{2}{+Module, -Default}
587True if predicates and operators in \arg{Default} are visible in
588\arg{Module}. Modules are returned in the same search order used for
589predicates and operators.  That is, \arg{Default} is first unified
590with \arg{Module}, followed by the depth-first transitive closure
591of import_module/2.
592
593    \predicate{add_import_module}{3}{+Module, +Import, +StartOrEnd}
594If \arg{Import} is not already an import module for \arg{Module}, add
595it to this list at the \const{start} or \const{end} depending on
596\arg{StartOrEnd}.  See also import_module/2 and delete_import_module/2.
597
598    \predicate{delete_import_module}{2}{+Module, +Import}
599Delete \arg{Import} from the list of import modules for \arg{Module}.
600Fails silently if \arg{Import} is not in the list.
601\end{description}
602
603One usage scenario of import modules is to define a module that is a
604copy of another, but where one or more predicates have an alternative
605definition.
606
607
608\section{Reserved Modules and using the `user' module}
609\label{sec:resmodules}
610
611As mentioned above, SWI-Prolog contains two special modules. The first
612one is the module \const{system}. This module contains all built-in
613predicates. Module \const{system} has no import module. The second
614special module is the module \const{user}. This module forms the initial
615working space of the user. Initially it is empty. The import module of
616module \const{user} is \const{system}, making all built-in predicates
617available.
618
619All other modules import from the module \const{user}. This implies they
620can use all predicates imported into \const{user} without explicitly
621importing them. If an application loads all modules from the
622\const{user} module using use_module/1, one achieves a scoping system
623similar to the C-language, where every module can access all exported
624predicates without any special precautions.
625
626
627\section{An alternative import/export interface}
628\label{sec:altmoduleapi}
629
630The use_module/1 predicate from \secref{import} defines import and
631export relations based on the filename from which a module is loaded. If
632modules are created differently, such as by asserting predicates into a
633new module as described in \secref{dynamic-modules}, this interface
634cannot be used. The interface below provides for import/export from
635modules that are not created using a module file.
636
637\begin{description}
638    \predicate{export}{1}{+PredicateIndicator, \ldots}
639Add predicates to the public list of the context module.  This implies
640the predicate will be imported into another module if this module is
641imported with use_module/[1,2].  Note that predicates are normally
642exported using the directive module/2. export/1 is meant to handle
643export from dynamically created modules.
644
645    \predicate{import}{1}{+PredicateIndicator, \ldots}
646Import predicates \arg{PredicateIndicator} into the current context
647module. \arg{PredicateIndicator} must specify the source module using
648the \mbox{<module>:<pi>} construct. Note that predicates are
649normally imported using one of the directives use_module/[1,2].
650The import/1 alternative is meant for handling imports into dynamically
651created modules.  See also export/1 and export_list/2.
652\end{description}
653
654
655\section{Dynamic Modules}               \label{sec:dynamic-modules}
656
657So far, we discussed modules that were created by loading a
658module file.  These modules have been introduced to facilitate the
659development of large applications.  The modules are fully defined at
660load-time of the application and normally will not change during
661execution.  Having the notion of a set of predicates as a
662self-contained world can be attractive for other purposes as well.
663For example, assume an application that can reason about multiple
664worlds.  It is attractive to store the data of a particular world in a
665module, so we extract information from a world simply by invoking
666goals in this world.
667
668Dynamic modules can easily be created.  Any built-in predicate that
669tries to locate a predicate in a specific module will create this
670module as a side-effect if it did not yet exist.  For example:
671
672\begin{code}
673?- assert(world_a:consistent),
674   set_prolog_flag(world_a:unknown, fail).
675\end{code}
676
677These calls create a module called `world_a' and make the call
678`world_a:consistent' succeed. Undefined predicates will not raise an
679exception for this module (see \prologflag{unknown}).
680
681Import and export from a dynamically created world can be achieved using
682import/1 and export/1 or by specifying the import module as described in
683\secref{importmodule}.
684
685\begin{code}
686?- world_b:export(solve/2).          % exports solve/2 from world_b
687?- world_c:import(world_b:solve/2).  % and import it to world_c
688\end{code}
689
690
691\section{Transparent predicates: definition and context module}
692\label{sec:ctxmodule}
693
694\textit{The `module-transparent' mechanism is still underlying the
695actual implementation.  Direct usage by programmers is deprecated.
696Please use meta_predicate/1 to deal with meta-predicates.}
697
698The qualification of module-sensitive arguments
699described in \secref{metapred} is realised using \jargon{transparent}
700predicates.  It is now deprecated to use this mechanism
701directly. However, studying the underlying mechanism helps to
702understand SWI-Prolog's modules.  In some respect, the transparent
703mechanism is more powerful than meta-predicate declarations.
704
705Each predicate of the program is assigned a module, called its
706\jargon{definition module}. The definition module of a predicate is
707always the module in which the predicate was originally defined. Each
708active goal in the Prolog system has a \jargon{context module} assigned
709to it.
710
711The context module is used to find predicates for a Prolog term. By
712default, the context module is the definition module of the predicate
713running the goal. For transparent predicates, however, this is the
714context module of the goal inherited from the parent goal. Below, we
715implement maplist/3 using the transparent mechanism. The code of
716maplist/3 and \nopredref{maplist_}{3} is the same as in
717\secref{metapred}, but now we must declare both the main predicate and
718the helper as transparent to avoid changing the context module when
719calling the helper.
720
721\begin{code}
722:- module(maplist, maplist/3).
723
724:- module_transparent
725	maplist/3,
726	maplist_/3.
727
728maplist(Goal, L1, L2) :-
729	maplist_(L1, L2, G).
730
731maplist_([], [], _).
732maplist_([H0|T0], [H|T], Goal) :-
733	call(Goal, H0, H),
734	maplist_(T0, T, Goal).
735\end{code}
736
737Note that \emph{any} call that translates terms into predicates is
738subject to the transparent mechanism, not just the terms passed to
739module-sensitive arguments. For example, the module below
740counts the number of unique atoms returned as bindings for a variable.
741It works as expected.  If we use the directive
742\exam{:- module_transparent count_atom_results/3.} instead,
743atom_result/2 is called wrongly in the module \emph{calling}
744\nopredref{count_atom_results}{3}. This can be solved using
745strip_module/3 to create a qualified goal and a non-transparent helper
746predicate that is defined in the same module.
747
748\begin{code}
749:- module(count_atom_results,
750	  [ count_atom_results/3
751	  ]).
752:- meta_predicate count_atom_results(-,0,-).
753
754count_atom_results(A, Goal, Count) :-
755	setof(A, atom_result(A, Goal), As), !,
756	length(As, Count).
757count_atom_results(_, _, 0).
758
759atom_result(Var, Goal) :-
760	call(Goal),
761	atom(Var).
762\end{code}
763
764The following predicates support the module-transparent interface:
765
766\begin{description}
767    \directive{module_transparent}{1}{+Preds}
768\arg{Preds} is a comma-separated list of name/arity pairs (like
769dynamic/1).  Each goal associated with a transparent-declared predicate
770will inherit the \jargon{context module} from its parent goal.
771
772    \predicate{context_module}{1}{-Module}
773Unify \arg{Module} with the context module of the current goal.
774context_module/1 itself is, of course, transparent.
775
776    \predicate{strip_module}{3}{+Term, -Module, -Plain}
777Used in module-transparent predicates or meta-predicates to extract the referenced
778module and plain term. If \arg{Term} is a module-qualified term, i.e.\
779of the format \arg{Module}:\arg{Plain}, \arg{Module} and \arg{Plain}
780are unified to these values.  Otherwise, \arg{Plain} is unified to
781\arg{Term} and \arg{Module} to the context module.
782\end{description}
783
784
785\section{Module properties}	\label{sec:manipmodule}
786
787The following predicates can be used to query the module system for
788reflexive programming:
789
790\begin{description}
791    \predicate[nondet]{current_module}{1}{?Module}
792True if \arg{Module} is a currently defined module. This predicate
793enumerates all modules, whether loaded from a file or created
794dynamically.  Note that modules cannot be destroyed in the current
795version of SWI-Prolog.
796
797    \predicate{module_property}{2}{?Module, ?Property}
798True if \arg{Property} is a property of \arg{Module}. Defined properties
799are:
800
801    \begin{description}
802	\termitem{class}{-Class}
803	True when \arg{Class} is the class of the module.  Defined
804	classes are
805	\begin{description}
806	    \termitem{user}{}
807	    Default for user-defined modules.
808	    \termitem{system}{}
809	    Module \const{system} and modules from \file{<home>/boot}.
810	    \termitem{library}{}
811	    Other modules from the system directories.
812	    \termitem{temporary}{}
813	    Module is temporary.
814	    \termitem{test}{}
815	    Modules that create tests.
816	    \termitem{development}{}
817	    Modules that only support the development environment.
818	\end{description}
819        \termitem{file}{?File}
820	True if \arg{Module} was loaded from \arg{File}.
821	\termitem{line_count}{-Line}
822	True if \arg{Module} was loaded from the N-th line of file.
823	\termitem{exports}{-ListOfPredicateIndicators}
824	True if \arg{Module} exports the given predicates. Predicate
825	indicators are in canonical form (i.e., always using name/arity
826	and never the DCG form name//arity). Future versions may also
827	use the DCG form. See also predicate_property/2.  Succeeds with
828	an empty list if the module exports no predicates.
829	\termitem{exported_operators}{-ListOfOperators}
830	True if \arg{Module} exports the given operators.  Each exported
831	operator is represented as a term \term{op}{Pri,Assoc,Name}.
832	Succeeds with an empty list if the module exports no operators.
833	\termitem{size}{-Bytes}
834	Total size in bytes used to represent the module.  This includes
835	the module itself, its (hash) tables and the summed size of
836	all predicates defined in this module. See also
837	the \term{size}{Bytes} property in predicate_property/2.
838	\termitem{program_size}{-Bytes}
839	Memory (in bytes) used for storing the predicates of this
840	module. This figure includes the predicate header and clauses.
841	\termitem{program_space}{-Bytes}
842	If present, this number limits the \const{program_size}.  See
843	set_module/1.
844	\termitem{last_modified_generation}{-Generation}
845	Integer expression the last database generation where a clause
846	was added or removed from a predicate that is implemented in
847	this module.  See also predicate_property/2.
848    \end{description}
849
850    \predicate{set_module}{1}{:Property}
851Modify properties of the module.  Currently, the following properties
852may be modified:
853
854    \begin{description}
855	\termitem{base}{+Base}
856Set the default import module of the current module to \arg{Module}.
857Typically, \arg{Module} is one of \const{user} or \const{system}.  See
858\secref{importmodule}.
859	\termitem{class}{+Class}
860Set the class of the module.  See module_property/2.
861	\termitem{program_space}{+Bytes}
862Maximum amount of memory used to store the predicates defined inside the
863module. Raises a permission error if the current usage is above the
864requested limit. Setting the limit to 0 (zero) removes the limit. An
865attempt to assert clauses that causes the limit to be exceeded causes a
866\term{resource_error}{program_space} exception. See assertz/1 and
867module_property/2.
868    \end{description}
869\end{description}
870
871
872\section{Compatibility of the Module System}	\label{sec:modulecompat}
873
874The SWI-Prolog module system is largely derived from the Quintus Prolog
875module system, which is also adopted by SICStus, Ciao and YAP.
876Originally, the mechanism for defining meta-predicates in SWI-Prolog was
877based on the module_transparent/1 directive and strip_module/3. Since
8785.7.4 it supports the de-facto standard meta_predicate/1 directive for
879implementing meta-predicates, providing much better compatibility.
880
881The support for the meta_predicate/1 mechanism, however, is considerably
882different. On most systems, the \emph{caller} of a meta-predicate is
883compiled differently to provide the required <module>:<term>
884qualification. This implies that the meta-declaration must be available
885to the compiler when compiling code that calls a meta-predicate. In
886practice, this implies that other systems pose the following
887restrictions on meta-predicates:
888
889\begin{itemize}
890    \item Modules that provide meta-predicates for a module to be compiled
891    must be loaded explicitly by that module.
892    \item The meta-predicate directives of exported predicates must follow
893    the module/2 directive immediately.
894    \item After changing a meta-declaration, all modules that \emph{call}
895    the modified predicates need to be recompiled.
896\end{itemize}
897
898In SWI-Prolog, meta-predicates are also \jargon{module-transparent}, and
899qualifying the module-sensitive arguments is done inside the
900meta-predicate. As a result, the caller need not be aware that it is
901calling a meta-predicate and none of the above restrictions hold for
902SWI-Prolog. However, code that aims at portability must obey the above
903rules.
904
905Other differences are listed below.
906
907\begin{itemize}
908    \item
909If a module does not define a predicate, it is searched for in the
910\jargon{import modules}. By default, the import module of any
911user-defined module is the \const{user} module. In turn, the
912\const{user} module imports from the module \const{system} that provides
913all built-in predicates.  The auto-import hierarchy can be changed
914using add_import_module/3 and delete_import_module/2.
915
916This mechanism can be used to realise a simple object-oriented system
917or a hierarchical module system.
918
919    \item
920Operator declarations are local to a module and may be exported. In
921Quintus and SICStus all operators are global.  YAP and Ciao also use
922local operators.  SWI-Prolog provides global operator declarations
923from within a module by explicitly qualifying the operator name with
924the \const{user} module.  I.e., operators are inherited from the
925\jargon{import modules} (see above).
926
927\begin{code}
928:- op(precedence, type, user:(operatorname)).
929\end{code}
930\end{itemize}
931
932