1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8% 
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License. 
13% 
14% The Original Code is  The ECLiPSe Constraint Logic Programming System. 
15% The Initial Developer of the Original Code is  Cisco Systems, Inc. 
16% Portions created by the Initial Developer are
17% Copyright (C) 2006 Cisco Systems, Inc.  All Rights Reserved.
18% 
19% Contributor(s): 
20% 
21% END LICENSE BLOCK
22
23:- comment(alias, "Modules").
24:- comment(summary, "Directives and built-ins related to the module system").
25:- comment(desc, html("See also the User Manual chapter about the module system.")).
26:- comment(categories, ["Built-In Predicates"]).
27
28:- tool((export) / 1).
29:- tool((import) / 1).
30:- tool((reexport) / 1).
31:- tool(erase_module / 1).
32:- tool((local) / 1).
33:- tool((lock) / 0).
34:- tool((lock_pass) / 1).
35:- tool(use_module / 1).
36:- tool(tool / 2).
37:- tool(tool_body / 3).
38
39:- comment(use_module / 1, [
40	summary:"Load and import the module from the given ModuleFile.",
41	amode:(use_module(++) is det),
42	desc:html("\
43   This is a combination of ensure_loaded/1 and import/1, i.e. it
44   loads a module file and imports everything the module exports.
45<P>
46   ModuleFile is a module name, a source file name, a library
47   specification (e.g. library(util)) or a list of such items. 
48   First, ModuleFile is converted to a file name and that file is
49   loaded, compiled or recompiled as with ensure_loaded/1.
50   Then, a module name is extracted from the base name of ModuleFile
51   (the loading is expected to create that module, i.e. the file is
52   expected to follow the naming convention for module files).
53   That module is then imported as with import/1.
54<P>
55   The rules for finding the source file from the ModuleFile specification
56   are the same as for ensure_loaded/1 and compile/1, i.e. object or
57   source file suffixes are appended, and the library path is searched
58   if the name is specified as library(FileName).
59"),
60	args:["ModuleFile" : "Atom, String, compound term library(Name), or a list of such."],
61	exceptions:[4 : "Module is not instantiated.",
62	    5 : "Module is instantiated, but not to an atom.",
63	    80 : "Module is not defined in the compiled file.",
64	    171 : "The file does not exist or is not readable."],
65	eg:"
66Success:
67    :- use_module(library(util)).
68    :- use_module(\"/usr/local/eclipse/lib/util\").
69    :- use_module(util).
70    :- use_module(\"util.pl\").
71
72
73Error:
74    :- use_module(M).                      (Error 4).
75    :- use_module(file(f)).                (Error 5).
76",
77    see_also:[module / 1, module/3, compile / 1, ensure_loaded / 1,
78	(import) / 1, lib / 1, existing_file/4]]).
79
80
81:- comment(create_module / 1, [
82	summary:"Create a module at runtime",
83	amode:(create_module(+) is det),
84	desc:html("\
85   create_module/1 creates the given module if it does not exist yet.
86   If the module already exists, an exception is raised (error 97).
87<P>
88   Note that modules are normally created by the compiler when it
89   encounters a module/1 directive.  The create_module/1 predicate
90   however creates modules dynamically at runtime.  The intended
91   applications are therefore mainly source processing tools, e.g.
92   compilers and loaders, or programs that need a clean name space
93   to store code and data.
94<P>
95   Note that the created module will by default import the language
96   module <CODE>eclipse_language</CODE>.  To create a completely empty
97   module, use the more general predicate create_module/3.  In fact, 
98   create_module/1 is defined as
99<PRE>
100   create_module(Module) :-
101       create_module(Module, [], eclipse_language).
102</PRE>
103   The system does not allow the atom [] to be used as a module name!
104"),
105	args:["Module" : "Atom."],
106	exceptions:[4 : "Module is not instantiated.",
107		5 : "Module is not an atom, or Module is the atom [].",
108		97 : "Module already exists."],
109	eg:"
110Success:
111    [eclipse 1]: create_module(m).
112    yes.
113    [eclipse 2]: export(data/1)@m.
114    yes.
115    [eclipse 3]: compile_term(data(99))@m.
116    yes.
117    [eclipse 4]: m:data(X).
118
119    X = 99
120    yes.
121    [eclipse 5]: erase_module(m).
122    yes.
123
124Error:
125    create_module(M).                   (Error 4).
126    create_module(1).                   (Error 5).
127    create_module(m), create_module(m). (Error 97).
128",
129	see_also:[module / 1, create_module/3, erase_module / 1,
130		get_module_info/3, current_module / 1]]).
131
132
133:- comment(create_module / 3, [
134	summary:"Create a module at runtime, with given exports and imports.",
135	amode:(create_module(+, ++, ++) is det),
136	desc:html("\
137   create_module/3 creates the given module if it does not exist yet.
138   If the module already exists, an exception is raised (error 97).
139<P>
140   Once the module is created, the module (or list of modules) given as
141   Imports is imported.
142<P>
143   The list Exports must contain valid export specifications as
144   described in export/1.  It defines the initial part of the module's
145   interface, subsequent export and reexport directives can add to that.
146<P>
147   Note that modules are normally created by the compiler when it
148   encounters a module/1 or module/3 directive.  The create_module/3
149   predicate however creates modules dynamically at runtime.  The
150   intended applications are therefore mainly source processing tools,
151   e.g. compilers and loaders, or programs that need a clean name
152   space to store code and data.
153<P>
154   The system does not allow the atom [] to be used as a module name!
155   If [] is given as the Imports argument, it indicates the empty list,
156   rather than a module with name [].
157"),
158	args:["Module" : "Atom.",
159		"Exports":"A list of export specifications as in export/1",
160		"Imports":"An atom or a list of atoms"
161	    ],
162	exceptions:[4 : "Module, Imports or Exports is not instantiated.",
163		5 : "Module is not an atom, or Module is the atom [].",
164		5 : "Imports is not an atom or list of atoms.",
165		5 : "Exports is not a list of exportable items.",
166		97 : "Module already exists."],
167	eg:"
168Success:
169    [eclipse 1]: create_module(m, [data/1], []).
170    yes.
171    [eclipse 2]: compile_term(data(99))@m.
172    yes.
173    [eclipse 3]: m:data(X).
174
175    X = 99
176    yes.
177    [eclipse 4]: erase_module(m).
178    yes.
179
180Error:
181    create_module(M, [], []).                (Error 4).
182    create_module(m, _, _).                  (Error 4).
183    create_module(m, [], library(iso)).      (Error 5).
184    create_module(m,[],[]), create_module(m,[],[]). (Error 97).
185",
186	see_also:[module / 1, module/3, create_module/1, erase_module / 1,
187		get_module_info/3, current_module / 1]]).
188
189
190:- comment(current_module / 1, [
191	summary:"Succeeds if Module is an existing module.
192
193",
194	amode:(current_module(-) is nondet),
195	amode:(current_module(+) is semidet),
196	desc:html("\
197   current_module/1 checks if there exists a module of a given name, or
198   finds on backtracking the names of all the existing modules.  A module
199   exists in the system iff it has been compiled or explicitely created.
200"),
201	args:["Module" : "Atom or variable."],
202	fail_if:"Fails if Module does not unify with an existing module",
203	exceptions:[5 : "Module is instantiated, but not to an atom."],
204	eg:"
205Success:
206
207    [eclipse]: current_module(M).
208    M = eclipse     More? (;)
209    M = sepia_kernel     More? (;)
210    M = eclipse_language     More? (;)
211    M = lists     More? (;)
212    M = profile     More? (;)
213    M = suspend     More? (;)    % type <cr>
214    yes.
215Fail:
216    current_module(not_a_module).
217Error:
218    current_module(\"eclipse\").         (Error 5).
219",
220	see_also:[create_module / 1, create_module/3, erase_module / 1,
221	    module / 1, get_module_info/3]]).
222
223
224:- comment(erase_module / 1, [
225	summary:"Erase the given module Module.  ",
226	amode:(erase_module(+) is det),
227	desc:html("\
228    erase_module/1 erases the given module.  This means that the module
229    will not exists any more.  All predicates and data (non-logical variables,
230    records, etc) defined in the module will be destroyed.  Subsequent calls
231    to the module's exported predicates will raise 'undefined procedure'
232    errors.
233<P>
234    If the Module does not exist, erase_module/1 simply succeeds.
235<P>
236    An error (101) is raised when trying to erase a module from within itself.
237<P>
238    Note that a module gets erased (and re-created) implicitly when the
239    compiler encounters a module/1 directive and that module already exists.
240"),
241	args:["Module" : "Atom."],
242	exceptions:[4 : "Module is not instantiated.", 5 : "Module is not an atom.", 101 : "Trying to erase Module from itself."],
243	eg:"
244Success:
245[eclipse]:  [user].
246 :- module(m).
247 :- export a/0.
248 a :- writeln(hello).
249 user        compiled 60 bytes in 0.00 seconds
250yes.
251[eclipse]: import a/0 from m.
252yes.
253[eclipse]: a.
254hello
255yes.
256[eclipse]: erase_module(m).
257yes.
258[eclipse]: a.
259calling an undefined procedure a in module eclipse
260
261Error:
262    erase_module(M).                   (Error 4).
263    erase_module(1).                   (Error 5).
264    erase_module(mod)@mod.             (Error 101).
265",
266	see_also:[module / 1, create_module / 1, create_module/3,
267	    current_module / 1, get_module_info/3]]).
268
269
270:- comment((export) / 1, [
271	% list only those that have no page of their own:
272	index:[chtab/2,syntax_option/1,initialization/1],
273	summary:"Exports from the caller module all items specified by SpecList.",
274	template:"export ++SpecList",
275	amode:(export(++) is det),
276	desc:html("\
277    To make definitions from one module accessible in others, they
278    have to be exported.  The following type of items can occur in
279    SpecList and can thus be exported:
280<DL>
281<DT><STRONG>Name/Arity</STRONG><DD>
282        procedure  specification
283
284<DT><STRONG>domain(Spec)</STRONG><DD>
285	domain declaration
286
287<DT><STRONG>struct(Prototype)</STRONG><DD>
288	structure declaration
289
290<DT><STRONG>op(Prec,Assoc,Name)</STRONG><DD>
291	operator declaration
292
293<DT><STRONG>chtab(Char,Class)</STRONG><DD>
294	character class declaration
295
296<DT><STRONG>syntax_option(Option)</STRONG><DD>
297	syntax option setting
298
299<DT><STRONG>macro(Functor,Transformation,Options)</STRONG><DD>
300	macro (input transformation) declaration
301
302<DT><STRONG>portray(Functor,Transformation,Options)</STRONG><DD>
303	portray (output transformation) declaration
304
305<DT><STRONG>initialization(Goal)</STRONG><DD>
306	initialization goal specification
307</DL>
308    SpecList is a comma-separated sequence of one or more of such items.
309    The export/1 primitive usually occurs as a directive in compiled
310    module files. It can occur anywhere in the file.
311<P>
312   <BIG>Exporting Procedures</BIG>
313<P>
314   A procedure can be (and usually is) declared as exported before it
315   is actually defined.  Export declarations should occur either at the
316   beginning of a module text, or just before the procedure definition,
317   e.g
318<PRE>
319       :- export double/2.
320       double(X, Y) :-
321	   Y is 2*X.
322</PRE>
323<P>
324   You can only export procedures that are defined in the exporting
325   module.  Imported procedures cannot be exported with export/1 (it
326   raises error 94) - use reexport/1 to do this.
327<P>
328   Declaring a procedure as exported will make it accessible to other modules.
329   That means that it can either be called with explicit module qualification
330   using :/2, or it can be imported and thus made visible elsewhere.
331<P>
332   Procedures can be imported and calls to them compiled before they have
333   been exported, e.g. when an importing module is compiled before the
334   exporting module.  This mechanism should be used only in exceptional
335   situations, normally the exporting module should be compiled first. 
336   The reason is that the compiler needs some information about the
337   predicate when compiling a call to it. If this information is not
338   available at call time, an incompatibility may occur later when the
339   exported definition is encountered.
340<P>
341   <BIG>Exporting Other Declarations</BIG>
342<P>
343   Exported structure, operator, syntax, macro and portray
344   declarations have the same effect as the corresponding local
345   declarations in the module where they occur.  In addition, they are
346   available in every module where they are imported.
347<P>
348   <BIG>Exporting Initializations</BIG>
349<P>
350   The exported initialization directive does not have any effect in
351   the exporting module, but <EM>only</EM> in the module where it is
352   imported.  The initialization goal is called once in the context of
353   every importing module.
354<P>
355   <BIG>Further Hints</BIG>
356<P>
357   All the export (and reexport) directives of a module together form
358   what is called the module's <EM>interface</EM>. The module interface
359   can be extracted from a module source file using the icompile/2
360   utility from library(document). The interface can also be retrieved
361   from a loaded module by calling get_module_info/3.
362<P>
363   Exporting the same item twice, or exporting something that has
364   previously been declared local, is accepted silently.
365<P>
366   The following primitives implicitly export items:  The module/3
367   directive and the create_module/3 predicate export the list of
368   items given in their second argument.  The tool/2 declaration
369   implicitly exports the tool body predicate.  Event handlers, error
370   handlers and interrupt handlers are implicitly exported by the
371   corresponding set_xxx_handler primitive.
372<P>
373   The export/1 primitive can not only occur as a directive but can also
374   be called at runtime.
375"),
376	args:["SpecList" : "One or a comma-separated sequence of valid export specifications"],
377	exceptions:[4 : "SpecList is not instantiated.",
378	    5 : "SpecList contains an invalid specification.",
379	    94 : "SpecList is already imported."],
380	eg:"
381% A module that exports a predicate and an operator:
382
383    :- module(m1).
384
385    :- export
386    	before/2,
387	op(700, xfx, before).
388
389    A before B :-
390    	A < B.
391
392% Using this module elsewhere:
393
394    :- module(m2).
395
396    :- import m1.    % or :- use_module(\".../m1...\").
397
398    main :-
399    	3 before 7.  % operator and procedure definition are visible!
400
401% Using before/2 without import, via explicit qualification:
402% We can call before/2, but we cannot use the infix syntax!
403
404    :- module(m3).
405
406    main :-
407    	m1:before(3,7).
408
409
410% Error cases:
411
412  :- export Q.                         (Error 4).
413  :- export p/a.                       (Error 5).
414  :- import p/1 from m.
415  :- export p/1.                       (Error 94).
416",
417	see_also:[(import) / 1, (reexport)/1, (local) / 1, use_module/1,
418	    module/1, (:)/2, get_module_info/3, document:icompile/1,
419	    document:icompile/2,
420	    domain/1, macro/3, op/3, portray/3, struct/1]]).
421
422
423:- comment((reexport) / 1, [
424	% list only those that have no page of their own:
425	index:[chtab/2,syntax_option/1,initialization/1],
426	summary:"Reexports a module's interface or a subset of it.",
427	template:["reexport +Module",
428		"reexport +SpecList from +Module",
429		"reexport +Module except +SpecList"],
430	amode:(reexport(+) is det),
431	desc:html("\
432    A reexport is conceptually an import combined with an export.  That
433    means that a reexported definition becomes visible inside the
434    reexporting module and is at the same time exported again.  A user
435    of a module's interface sees virtually no difference between
436    exported and reexported definitions.  Reexporting is a flexible
437    way to create tailored module interfaces, e.g. extend the interface
438    of an existing module, restrict it, combine features from several
439    modules, or create specific modifications of existing modules.
440<P>
441    The reexport declaration comes in three flavours. To reexport the
442    complete interface of another module, use
443<PRE>
444	:- reexport amodule.
445</PRE>
446    However, often it is desirable or necessary to restrict the set of
447    reexported items.  This can be done in two ways, either by
448    explicitly listing the items to reexport, e.g.
449<PRE>
450	:- reexport useful/3, good/1 from amodule.
451</PRE>
452    or else by listing the exception that should not be reexported, e.g.
453<PRE>
454	:- reexport amodule except useless/3, unwanted/1.
455</PRE>
456   SpecList can contain any valid export specification, i.e.
457<DL>
458<DT><STRONG>Name/Arity</STRONG><DD>
459        procedure  specification
460
461<DT><STRONG>domain(Spec)</STRONG><DD>
462	domain declaration
463
464<DT><STRONG>struct(Prototype)</STRONG><DD>
465	structure declaration
466
467<DT><STRONG>op(Prec,Assoc,Name)</STRONG><DD>
468	operator declaration
469
470<DT><STRONG>chtab(Char,Class)</STRONG><DD>
471	character class declaration
472
473<DT><STRONG>syntax_option(Option)</STRONG><DD>
474	syntax option setting
475
476<DT><STRONG>macro(Functor,Transformation,Options)</STRONG><DD>
477	macro (input transformation) declaration
478
479<DT><STRONG>portray(Functor,Transformation,Options)</STRONG><DD>
480	portray (output transformation) declaration
481
482<DT><STRONG>initialization(Goal)</STRONG><DD>
483	initialization goal specification
484</DL>
485    Procedure specifications must be fully instantiated with name and
486    arity. All other specifications may contain anonymous variables
487    which serve as wildcards when matching the exports.  For example,
488    to reexport all operator declarations of another module use
489<PRE>
490	:- reexport op(_,_,_) from amodule.
491</PRE>
492    To reexport only the operator declaration for the operator 'before',
493    whatever it is defined to, use
494<PRE>
495	:- reexport op(_,_,before) from amodule.
496</PRE>
497    or to prevent a macro declaration for internal/3 from being reexported, use
498<PRE>
499	:- reexport amodule except macro(internal/3,_,_).
500</PRE>
501<P>
502   When explicitly reexporting procedures, it is required that they are
503   actually exported from the other module. In all other cases, the items
504   listed in SpecList do not have to correspond to actually exported items
505   in the other module.
506<P>
507   Reexported procedures are made accessible to other modules in the
508   same way as exported ones.  That means they can either be called by
509   explicitly qualifying them with the name of the reexporting module
510   (using :/2), or they can be imported from the reexporting module
511   and thus made visible elsewhere.
512<P>
513   All the export (and reexport) directive of a module together form
514   what is called the module's <EM>interface</EM>. The module interface
515   can be extracted from a module source file using the icompile/2
516   utility from library(document). The interface can also be retrieved
517   from a loaded module by calling get_module_info/3.
518<P>
519   Rexporting the same item twice, or reexporting something that has
520   previously been declared imported, is accepted silently.
521<P>
522   Reexporting is not compatible with a local definition of the same
523   name (because reexport always implies an import as well), it raises
524   error 92.
525<P>
526   The reexport/1 primitive can not only occur as a directive but can also
527   be called at runtime.
528"),
529	args:["Module" : "Atom.",
530	    "SpecList" : "One or a comma-separated sequence of valid export specifications"],
531	exceptions:[4 : "SpecList or Module is insufficiently instantiated.",
532	    5 : "Module is not an atom.",
533	    5 : "SpecList contains an invalid specification.",
534	    92 : "One of the reexported procedures has the same name as a local procedure."],
535	eg:"
536% A module that is like m1 but adds something extra:
537
538    :- module(m).
539    :- reexport m1.
540    :- export extra/1.
541    extra(99).
542
543
544% A module that makes a subset of m1 available:
545
546    :- module(m).
547    :- reexport m1 except useless/3, unwanted/1.
548
549
550% A module that combines m1 and m2:
551
552    :- module(m).
553    :- reexport m1 except also_in_m2/2.
554    :- reexport m2.
555
556
557% A module that modifies m1:
558
559    :- module(m).
560    :- reexport m1 except different/1.
561    :- export different/1.
562    different(better).
563
564
565% Error cases:
566
567  :- reexport Q.                         (Error 4).
568  :- reexport p/a.                       (Error 5).
569
570  :- local p/1.
571  :- export p/1.                         (Error 92).
572",
573	see_also:[(import) / 1, (export)/1, (local) / 1, use_module/1,
574	    module/1, (:)/2, get_module_info/3, document:icompile/1,
575	    document:icompile/2,
576	    domain/1, macro/3, op/3, portray/3, struct/1]]).
577
578
579
580:- comment((import) / 1, [
581	summary:"Import a module, or import certain procedures from a module.",
582	template:["import +Module", "import +PredSpecs from +Module"],
583	amode:(import(++) is det),
584	desc:html("\
585   Importing is the way to make definitions from another module visible
586   as if they were local definitions. Only items that have been exported
587   from another module can be imported. Imports should usually be done
588   at the beginning of module texts.
589<P>
590   <BIG>Importing a Module as a Whole</BIG>
591<P>
592   If the first form of import is used, e.g.
593<PRE>
594   	:- import amodule.
595</PRE>
596   then all of the specified module's interface (i.e. everything that
597   is exported or reexported there) gets imported.
598<P>
599   Note that the module to import must already have been loaded, e.g. 
600   via compile/1 or ensure_loaded/1.  To simplify this, you can use
601   use_module/1 which is simply a combination of ensure_loaded/1 and
602   import/1.  If an attempt is make to import a module that does not
603   exist yet, the system tries to create it by trying to load a
604   library of that name. 
605<P>
606   Note that procedure imports a treated slightly differently from
607   other (e.g.  structure declaration) imports:  While other imports
608   have an immediate effect (e.g.  making the structure declaration
609   available), procedures are actually imported lazily:  they are only
610   made visible when they are referred to (e.g.  called) subsequently
611   in the importing module.  This has the advantage that import
612   ambiguities (i.e.  the same procedure is exported from multiple
613   imported modules) do not pose any problem as long as the ambiguous
614   procedure is not actually used.  When it is used, however, the
615   system will report the conflict.  The conflict can then either be
616   resolved by using the <CODE>import ... from ...</CODE> construct,
617   or it can be avoided by using explicit module qualification via :/2
618   everywhere.
619<P>
620   When a local procedure is defined while a procedure with the same
621   name could be lazily imported from an imported module, the system
622   issues a warning (or even an error in the case of built-ins).  If
623   that was the intention, the warning should be suppressed by using
624   an explicit local-declaration.
625<P>
626   <BIG>Importing Specific Procedures from a Module</BIG>
627<P>
628   An example of the second form of the import declaration is
629<PRE>
630   	:- import p/3,q/1 from amodule.
631</PRE>
632   This causes only the specified procedures to be imported from the
633   given module.  Unlike above, this import has an immediate effect,
634   and any attempt to import the same name from elsewhere, or to declare
635   a local procedure of the same name will raise an error 94.
636   Only procedures can be imported using this form of import/1.
637<P>
638   Another difference compared to the first form of import/1 is that
639   the module from which we import does not have to exist yet, and no
640   attempt is made to load the module. This is therefore a way to overcome
641   the otherwise enforced export-before-import rule and it allows a
642   certain degree of circularity in the export-import relationship
643   between modules. However, it is usually considered better programming
644   style to have a strictly hierarchical module structure rather than
645   circular dependencies, and to always build a new module on top of
646   a self-contained set of more basic modules.
647<P>
648   Note that when the compiler compiles a call to an imported procedure
649   whose export is not yet known, it may use the wrong calling convention.
650   This will lead to an incompatibility error later when the export
651   becomes known. Forward declarations like tool/2 and external/1 can
652   sometimes be used to prevent this problem.
653<P>
654   <BIG>Implicit Imports</BIG>
655<P>
656   Modules are implicitly imported by the module/3 and create_module/3
657   primitives, which import the modules given in their third argument. 
658   Modules created with module/1 or create_module/1 implicitly import
659   the module <CODE>eclipse_language</CODE>.
660"),
661	args:["Module" : "Atom.",
662		"PredSpecs":"One or more comma-separated terms of the form Name/Arity"],
663	exceptions:[4 : "Module is not instantiated.",
664	    5 : "Module is instantiated, but not to an atom.",
665	    80 : "Library file does not define Module.",
666	    171 : "Library file does not exist.",
667	    92 : "Conflict with local definition.",
668	    93 : "Conflict with exported definition.",
669	    94 : "Conflict with another imported procedure."],
670	eg:"
671% A module that exports a predicate and an operator:
672
673    :- module(m1).
674
675    :- export
676    	before/2,
677	op(700, xfx, before).
678
679    A before B :-
680    	A < B.
681
682% Importing this module elsewhere:
683
684    :- module(m2).
685
686    :- import m1.    % or :- use_module(\".../m1...\").
687
688    main :-
689    	3 before 7.  % operator and procedure definition are visible!
690
691
692% Importing a procedure:
693
694    :- module(m3).
695
696    :- import before/2 from m1.
697
698    main :-
699    	before(3,7).  % only procedure definition is visible!
700
701
702% Error cases:
703
704     :- import L.                                     (Error 4).
705     :- import 1.                                     (Error 5).
706     :- import a,b.                                   (Error 5).
707     :- import op(X,Y,before) from eclipse_language.  (Error 5).
708     :- import xxxx.                                  (Error 171).
709
710     :- import p/1 from a.
711     :- import p/1 from b.                            (Error 94).
712
713     :- export p/1.
714     :- import p/1 from b.                            (Error 93).
715
716     p(99).
717     :- import p/1 from b.                            (Error 92).
718",
719	see_also:[(export) / 1, (reexport) / 1, (local) / 1,
720		get_module_info/3, module/1, create_module/3]]).
721
722
723:- comment((local) / 1, [
724	% list only those that have no page of their own:
725	index:[record/1,chtab/2,syntax_option/1,initialization/1,finalization/1],
726	summary:"Declare all items specified by SpecList as local to the caller module.",
727	template:"local +SpecList",
728	amode:(local(++) is det),
729	desc:html("
730    This declaration is used to declare the visibility of procedures
731    and other items as local to the caller module.  SpecList is a
732    comma-separated sequence of one or more items of the following form:
733<DL>
734<DT><STRONG>Name/Arity</STRONG><DD>
735        procedure specification
736
737<DT><STRONG>domain(Spec)</STRONG><DD>
738	domain declaration
739
740<DT><STRONG>struct(Prototype)</STRONG><DD>
741	structure declaration
742
743<DT><STRONG>variable(Name)</STRONG><DD>
744	non-logical variable declaration
745
746<DT><STRONG>variable(Name,InitialValue)</STRONG><DD>
747	non-logical variable declaration with initial value
748
749<DT><STRONG>reference(Name)</STRONG><DD>
750	reference declaration
751
752<DT><STRONG>reference(Name,InitialValue)</STRONG><DD>
753	reference declaration with initial value (ground term)
754
755<DT><STRONG>array(Name)</STRONG><DD>
756	untyped non-logical array declaration
757
758<DT><STRONG>array(Name,Type)</STRONG><DD>
759	typed non-logical array declaration
760
761<DT><STRONG>record(Name)</STRONG><DD>
762	record key declaration
763
764<DT><STRONG>shelf(Name,InitialValue)</STRONG><DD>
765	shelf name declaration with initial value
766
767<DT><STRONG>store(Name)</STRONG><DD>
768	store name declaration
769
770<DT><STRONG>op(Prec,Assoc,Name)</STRONG><DD>
771	operator declaration
772
773<DT><STRONG>chtab(Char,Class)</STRONG><DD>
774	character class declaration
775
776<DT><STRONG>syntax_option(Option)</STRONG><DD>
777	syntax option setting
778
779<DT><STRONG>macro(Functor,Transformation,Options)</STRONG><DD>
780	macro (input transformation) declaration
781
782<DT><STRONG>portray(Functor,Transformation,Options)</STRONG><DD>
783	portray (output transformation) declaration
784
785<DT><STRONG>initialization(Goal)</STRONG><DD>
786	goal to be executed just after the module has been loaded
787
788<DT><STRONG>finalization(Goal)</STRONG><DD>
789	goal to be executed just before the module is erased (whether
790	explicitly, or implicitly during recompilation or exiting ECLiPSe)
791</DL>
792
793   The effect of the local-declaration is that the declared items are
794   only visible inside the module where they have been declared.
795<P>
796   <BIG>Local Procedures</BIG>
797<P>
798   For procedures, the local-declaration is normally redundant because
799   local visibility is the default.  However, it might be necessary to
800   explicitly declare a procedure as local to resolve a name conflict
801   when an imported module exports a procedure of the same name.
802<P>
803   Local declarations should be placed at the beginning of a module text.
804   They must occur before the first reference to the declared prodecure:
805<P>
806   A procedure can have four kinds of visibility in a given module:
807   local, exported, imported or reexported.  A local-declaration is
808   silently ignored if the procedure has already been exported before.
809   If a procedure of the given name has already been imported or
810   reexported, the local-declaration raises an error 94.
811   If there is one or more imported modules which export a procedure of
812   the same name, these all get hidden silently by the local declaration.
813<P>
814   A local procedure can only be called from within the module where it is
815   defined, even when explicit module qualification via :/2 is used.
816<P>
817   <BIG>Local Initialization and Finalization</BIG>
818<P>
819   The local initialization declaration is used to specify an initialization
820   goal. All initialization goals which occur within a compilation unit
821   (file or module), will be executed just after this compilation unit
822   has been loaded by the system.
823<P>
824   A finalization goal will be executed just before the module containing
825   the declaration gets erased. This can happen either explicitly through
826   erase_module/1, or implicitly when the module gets recompiled or when
827   ECLiPSe exits. Finalisation goals should not do any I/O because in the
828   case of an embedded ECLiPSe, I/O may no longer be available at
829   finalisation time.
830<P>
831   <BIG>Other Local Items</BIG>
832<P>
833   All other local declarations also have an effect only in the module
834   where they occur.  Some of them have corresponding export-variants.
835<P>
836   <BIG>Further Hints</BIG>
837<P>
838   The local/1 primitive can not only occur as a directive but can also
839   be called at runtime.
840<P>
841   Duplicate local declarations are accepted silently.
842"),
843	args:["SpecList" : "One or a comma-separated sequence of valid local specifications"],
844	exceptions:[4 : "SpecList is not instantiated.",
845	    5 : "SpecList is instantiated, but not to a sequence of valid local specifications.",
846	    94 : "SpecList is already imported."],
847	eg:"
848% Normally, local declarations for predicates are redundant:
849  :- module(m).
850
851  :- local p/1.         % can be omitted since the default is local
852  p(99).
853
854
855% Redefining a built-in predicate:
856
857    :- module(m)
858    :- local writeln/1.   % stop writeln/1 from being imported
859
860    main :-
861       writeln(hello).    % local-declaration must be before this use!
862
863    writeln(X) :-         % the local version
864       printf(\"I don't like the normal writeln/1 predicate: %w%n\",[X]).
865
866
867% Redefining an imported predicate:
868
869    :- module(m)
870    :- lib(lists).        % module 'lists' defines a predicate subtract/3
871    :- local subtract/3.  % stop subtract/3 being imported from 'lists'
872
873    decr(N, N1) :-
874       subtract(N,1,N1).  % local-declaration must be before this use!
875
876    subtract(X,Y,Z) :-    % the local version of subtract/3
877       Z is X-Y.
878
879
880% Other local declarations:
881
882   :- local
883   	op(500, xfx, before),
884	struct(book(author,title,publisher)).
885
886   :- local initialization(writeln(\"I am being initialized!\")).
887
888
889% Error cases:
890
891  :- local P.                           (Error 4).
892  :- local p/a.                         (Error 5).
893  :- (import p/0 from m), local(p/0)    (Error 94).
894",
895	see_also:[(export) / 1, (reexport) / 1, (import) / 1, module/1,
896	    array/1, array/2, domain/1, macro/3, op/3, portray/3, reference/1,
897	    reference/2, set_flag/2,
898	    store/1, struct/1, variable/1, variable/2]]).
899
900
901:- comment(lock / 0, [
902	summary:"Locks access to internals of the current module",
903	amode:(lock is det),
904	desc:html("\
905    Used to forbid access from outside the current module to its internals,
906    except through the module interface (i.e. its exports).
907<P>
908    This primitive is usually used a directive in the source code of the
909    module to be locked.
910<P>
911    A module locked with lock/0 cannot be unlocked.  Repeated locking
912    (from within the module) is silently accepted.
913<P>
914"),
915	eg:"
916    % After compiling the following code:
917     :- module(m).
918     :- export pub/0.
919     pub :- writeln(pub).
920     priv :- writeln(priv).
921     :- lock.
922
923
924    ?- module(m).
925    trying to access a locked module in module(m)
926
927    ?- call(pub) @ m.
928    pub
929    yes.
930
931    ?- call(priv) @ m.
932    trying to access a locked module in priv
933
934    ?- assert(foo) @ m.
935    trying to access a locked module in assert_(foo, m)
936
937",
938	see_also:[lock_pass / 1, unlock / 2, get_module_info/3]]).
939
940
941:- comment(lock_pass / 1, [
942	summary:"Locks access to internals of the current module",
943	amode:(lock_pass(+) is det),
944	desc:html("\
945    Used to forbid access from outside the current module to its internals,
946    except through the module interface (i.e. its exports).
947<P>
948    This primitive is usually used a directive in the source code of the
949    module to be locked.
950<P>
951    A module locked with lock_pass/1 can be unlocked using unlock/2, and
952    giving the same pass-string that was used in locking.  The pass-string
953    can be changed by calling lock_pass/1 again from within the module.
954<P>
955"),
956	eg:"
957    % After compiling the following code:
958     :- module(m).
959     :- export pub/0.
960     pub :- writeln(pub).
961     priv :- writeln(priv).
962     :- lock_pass(\"secret\").
963
964
965    ?- module(m).
966    trying to access a locked module in module(m)
967
968    ?- call(pub) @ m.
969    pub
970    yes.
971
972    ?- call(priv) @ m.
973    trying to access a locked module in priv
974
975    ?- assert(foo) @ m.
976    trying to access a locked module in assert_(foo, m)
977
978    ?- unlock(m, \"secret\").
979    yes.
980
981    ?- call(priv) @ m.
982    priv
983    yes.
984
985    ?- assert(foo) @ m.
986    yes.
987
988",
989	see_also:[lock/ 0, unlock / 2, get_module_info/3]]).
990
991
992:- comment(tool / 2, [
993	summary:"Declares PredSpecI as a tool interface procedure and PredSpecB as its body
994procedure.
995",
996	amode:(tool(++,++) is det),
997	desc:html("   It defines PredSpecI as a tool interface procedure in the caller module
998   and declares PredSpecB as its body procedure.  The arity of PredSpecB
999   must be one higher than the arity of PredSpecI, otherwise an exception
1000   is raised.  This is because when PredSpecI is called, the system puts
1001   the name of the caller module in the additional argument and calls
1002   PredSpecB.
1003<P>
1004   The default visibility for the interface procedure is local.
1005   The body procedure gets exported implicitly.
1006<P>
1007   The tool/2 declaration can be used before the body procedure is defined.
1008<P>
1009   If PredSpecI already exists and if the system has already compiled some
1010   calls to it, tool/2 gives error 62 (``inconsistent procedure
1011   redefinition'') since the system cannot provide the caller's home module
1012   for calls which are already compiled.
1013<P>
1014   Therefore, the tool/2 declaration should be always textually precede the
1015   first call to enable to compiler to compile the call correctly.
1016<P>
1017"),
1018	args:["PredSpecI" : "Expression of the form Atom/Integer.", "PredSpecB" : "Expression of the form Atom/Integer."],
1019	exceptions:[4 : "Either PredSpecI or PredSpecB is not instantiated.",
1020	5 : "Either PredSpecI or PredSpecB is instantiated, but not to an    expression of the form Atom/Integer.",
1021	6 : "The arity of PredSpecB is not one greater than that of    PredSpecI.",
1022	62 : "A call to PredSpec has already been compiled before the    tool declaration (``inconsistent procedure redefinition'')."],
1023	eg:"
1024% A typical meta-predicate, wrong and right way:
1025
1026    [eclipse 1]: [user].
1027	:- module(m1).
1028	:- export twice/1.
1029	twice(P):-
1030	    call(P),
1031	    call(P).
1032    yes.
1033
1034    [eclipse 2]: [user].
1035     p(1).
1036    yes.
1037
1038    [eclipse 3]: import twice/1 from m1.
1039    yes.
1040
1041    [eclipse 4]: twice(p(X)).
1042    calling an undefined procedure p(X) in module m1
1043    yes.
1044
1045    [eclipse 5]: [user].
1046	:- module(m1).
1047	:- export twice/1.
1048	:- tool(twice/1,twice_body/2).
1049	twice_body(P,M):-
1050	    call(P)@M,
1051	    call(P)@M.
1052    yes.
1053
1054    [eclipse 6]: twice(p(X)).
1055    X = 1
1056    yes.
1057
1058
1059% define a predicate that prints its caller module:
1060
1061    [eclipse]: tool(where_am_i/0, writeln/1).
1062    yes.
1063
1064    [eclipse]: where_am_i.
1065    eclipse
1066    yes.
1067
1068
1069% Error:
1070     tool(L, tb/1).                   (Error 4).
1071     tool(ti/0, L).                   (Error 4).
1072     tool(ti, tb/1).                  (Error 5).
1073     tool(ti/0, tb).                  (Error 5).
1074     tool(ti/0, tb/2).                (Error 6).
1075
1076     [eclipse]: [user].
1077      p :- ti. % call compiled before tool declaration
1078      user        compiled 32 bytes in 0.02 seconds
1079     yes.
1080     [eclipse]: tool(ti/0, tb/1).     (Error 62).
1081",
1082	see_also:[tool_body / 3, (@)/2]]).
1083
1084:- comment(tool_body / 3, [
1085	summary:"Succeeds if PredSpecI is a tool interface procedure, PredSpecB is its body
1086procedure, and Module the module where it is defined.
1087
1088",
1089	amode:(tool_body(++, -,-) is det),
1090	desc:html("   To a given tool interface procedure it finds the corresponding body
1091   procedure and the module where it is defined.
1092
1093<P>
1094"),
1095	args:["PredSpecI" : "Expression of the form Atom/Integer.", "PredSpecB" : "Expression of the form Atom/Integer.", "Module" : "Atom or variable."],
1096	exceptions:[4 : "PredSpecI is not instantiated.", 5 : "Either PredSpecI or PredSpecB is instantiated, but not to    the form Atom/Integer.", 91 : "PredSpecI is not a tool interface procedure."],
1097	eg:"
1098Success:
1099      [eclipse]: tool_body(write/1, P, M), (import P from M).
1100      P = write_ / 2             % find the body
1101      M = sepia_kernel           %   procedure and
1102      yes.                       %   import it
1103
1104Fail:
1105      tool_body(write/1, true/0, M).
1106
1107Error:
1108      tool_body(L, P, M).                   (Error 4).
1109      tool_body(\"current_functor/1\", P, M). (Error 5).
1110      tool_body(current_functor/1, P, M).   (Error 91).
1111
1112
1113
1114",
1115	see_also:[tool / 2]]).
1116
1117:- comment(unlock / 2, [
1118	summary:"Unlocks the access to the module Module, if the password given in Password
1119is correct
1120
1121",
1122	amode:(unlock(+,+) is det),
1123	desc:html("\
1124   unlock(Module, Password) unlock a module previously locked with
1125   lock_pass(Password).  The access to the module is now again possible.
1126
1127<P>
1128   An error is raised (and the module not unlocked) when trying to unlock a
1129   module with a wrong password or when trying to unlock a module locked
1130   with lock/0.
1131
1132<P>
1133"),
1134	args:["Module" : "Atom.", "Password" : "String."],
1135	exceptions:[4 : "Module or Password is/are not instantiated.",
1136		5 : "Module is instantiated, but not to an atom or Password is    instantiated but not to a string.",
1137		80 : "Module is not a module.",
1138		82 : "Trying to access a locked module Module",
1139		98 : "Key not correct"],
1140	eg:"
1141    % After compiling the following code:
1142     :- module(m).
1143     :- export pub/0.
1144     pub :- writeln(pub).
1145     priv :- writeln(priv).
1146     :- lock_pass(\"secret\").
1147
1148
1149    ?- module(m).
1150    trying to access a locked module in module(m)
1151
1152    ?- call(pub) @ m.
1153    pub
1154    yes.
1155
1156    ?- call(priv) @ m.
1157    trying to access a locked module in priv
1158
1159    ?- assert(foo) @ m.
1160    trying to access a locked module in assert_(foo, m)
1161
1162    ?- unlock(m, \"pass\").
1163    key not correct in unlock(m, \"pass\")
1164
1165    ?- unlock(m, \"secret\").
1166    yes.
1167
1168    ?- call(priv) @ m.
1169    priv
1170    yes.
1171
1172    ?- assert(foo) @ m.
1173    yes.
1174",
1175	see_also:[lock/0, lock_pass / 1, get_module_info/3]]).
1176
1177
1178:- comment(module / 1, [
1179	summary:"Begin of the definition of module Module.",
1180	amode:(module(+) is det),
1181	desc:html("\
1182   This is a directive that can occur only in a compiled file.  If Module
1183   is an existing module, it is first erased.  Then a new module is created
1184   and all subsequent definitions, declarations and directives are taken
1185   in the context of that new module.
1186<P>
1187   The new module implicitly imports the module <CODE>eclipse_language</CODE>,
1188   which means that all ECLiPSe built-ins are visible there.
1189<P>
1190   <CODE>module(m)</CODE> is equivalent to <CODE>module(m,[],eclipse_language)</CODE>.
1191<P>
1192   Note that module/1 is not a predicate, it can only occur as a
1193   directive in a compiled file.  However, the console based ECLiPSe
1194   toplevel also interprets module/1 commands, but in the following
1195   way:  when the module already exists, the toplevel-module (i.e. 
1196   the context in which toplevel queries are interpreted) is changed
1197   to this module.  When the module does not exist, it gets created
1198   and a warning is issued.
1199<P>
1200   The system does not allow the atom [] to be used as a module name!
1201"),
1202	args:["Module" : "Atom."],
1203	exceptions:[4 : "Module is not instantiated.",
1204		5 : "Module is not an atom, or Module is the atom [].",
1205		68 : "When called from Prolog.",
1206		82 : "Module is locked."],
1207	eg:"
1208% A very small module:
1209     :- module(m).
1210     :- export hello/0.
1211     hello :- writeln(\"Welcome to module m!\").
1212",
1213	see_also:[module / 1, module / 3, create_module / 1, create_module/3,
1214		erase_module / 1, current_module / 1, (export)/1]]).
1215
1216
1217/***********************************************************************
1218:- comment(module / 2, [
1219	summary:"Begin the definition of module Module and define its interface.",
1220	amode:(module(+,++) is det),
1221	desc:html("\
1222   This variant of the module-directive exists mainly for compatibility
1223   with other Prolog systems.
1224<P>
1225   This is a directive that can occur only in a compiled file.  If Module
1226   is an existing module, it is first erased.  Then a new module is created
1227   and all subsequent definitions, declarations and directives are taken
1228   in the context of that new module.
1229<P>
1230   The list Exports must contain valid export specifications as
1231   described in export/1.  It defines the first part of the module's
1232   interface, subsequent export and reexport directives can add to that.
1233<P>
1234   The new module implicitly imports the module <CODE>eclipse_language</CODE>,
1235   which means that all ECLiPSe built-ins are visible there.
1236<P>
1237   The system does not allow the atom [] to be used as a module name!
1238"),
1239	args:["Module" : "Atom.",
1240		"Exports":"A list of export specifications."],
1241	exceptions:[4 : "Module is not instantiated.",
1242		5 : "Module is not an atom, or Module is the atom [].",
1243		5 : "Exports is not a list of valid export specifications.",
1244		68 : "When called from Prolog.",
1245		82 : "Module is locked."],
1246	eg:"
1247Success:
1248     [eclipse 2]: [user].
1249     :- module(m, [op(700, xf, there), p/1]).
1250     p(X) :- writeln(X).
1251      user compiled 56 bytes in 0.03 seconds
1252     yes.
1253     [eclipse 3]: p(hello there).
1254     syntax error: postfix/infix operator expected
1255     | p(hello there).
1256     |             ^ here
1257     [eclipse 3]: use_module(m).
1258
1259     yes.
1260     [eclipse 4]: p(hello there).
1261     hello there
1262
1263     yes.
1264",
1265	see_also:[module / 1, module / 3, create_module / 1, create_module/3,
1266		erase_module / 1, current_module / 1, (export)/1]]).
1267***********************************************************************/
1268
1269:- comment(module / 3, [
1270	summary:"Begin the definition of module Module, define some of its exports and the language it is written in.",
1271	amode:(module(+,++,++) is det),
1272	desc:html("\
1273   This is a directive that can occur only in a compiled file.  If Module
1274   is an existing module, it is first erased.  Then a new module is created
1275   and all subsequent definitions, declarations and directives are taken
1276   in the context of that new module.
1277<P>
1278   The list Exports must contain valid export specifications as
1279   described in export/1.  It defines the first part of the module's
1280   interface, subsequent export and reexport directives can add to that.
1281<P>
1282   Unlike with module/1, the new module does <EM>not</EM> implicitly import anything.
1283   In particular, no built-in predicates are available inside the module
1284   unless a language-module is specified in the Language argument.
1285   This module (or a list of them) is imported just after the new module
1286   is created.
1287<P>
1288   The main use of this feature is to write different parts of a program
1289   in different language dialects. For example, a module that contains code
1290   written in ISO-Prolog should be encapsulated in a module starting with:
1291<PRE>
1292	:- module(mymodule, [], iso).
1293</PRE>
1294   In this module, ISO language features can be used, but not (all)
1295   Eclipse features.
1296<P>
1297   The system does not allow the atom [] to be used as a module name!
1298   If [] is given as the Language argument, it indicates the empty list,
1299   rather than a module with name [].
1300"),
1301	args:["Module" : "Atom.",
1302		"Exports":"A list of export specifications.",
1303		"Language":"An atom or a list of atoms."],
1304	exceptions:[4 : "Module is not instantiated.",
1305		5 : "Module is not an atom, or Module is the atom [].",
1306		68 : "When called from Prolog.",
1307		82 : "Module is locked."],
1308	eg:"
1309% A module in C-Prolog syntax:
1310
1311     :- module(m, [p/1], cprolog).
1312
1313     p(\"this is a list not a string\").
1314",
1315	see_also:[module / 1, create_module / 1, create_module/3,
1316		erase_module / 1, current_module / 1, (export)/1]]).
1317
1318
1319:- comment(get_module_info / 3, [
1320	summary:"Retrieves information about a loaded module.",
1321	amode:(get_module_info(+,-,-) is nondet),
1322	amode:(get_module_info(+,+,-) is semidet),
1323	desc:html("\
1324   This utility can retrieve information about any module that is currently
1325   loaded into the system. The information that can be requested is:
1326<DL>
1327<DT><STRONG>raw_interface</STRONG> (list of export/1 and reexport/1)<DD>
1328	this returns a list of all the export and reexport directives that
1329	occurred in the definition of the module and thus comprise the module's
1330	interface.
1331<DT><STRONG>interface</STRONG> (list of export/1)<DD>
1332	Like raw_interface, but all reexports are replaced by the
1333	actual exports which result from them.
1334<DT><STRONG>imports</STRONG> (list of modules)<DD>
1335	a list of the modules that have been imported as a whole.
1336<DT><STRONG>locked</STRONG> (on/off)<DD>
1337	indicates whether the module is locked or unlocked.
1338</DL>
1339"),
1340	args:["Module" : "Atom.",
1341		"What":"An atom.",
1342		"Info":"A variable."],
1343	exceptions:[4 : "Module is not instantiated.",
1344		5 : "Module is not an atom.",
1345		80 : "Module is not a loaded module."],
1346	eg:"
1347[eclipse 1]: get_module_info(lists, X,Y).
1348
1349X = raw_interface
1350Y = [export maplist / 3, export checklist / 2, ...]
1351
1352X = interface
1353Y = [export reverse / 2, export subtract / 3, ...]
1354
1355X = imports
1356Y = [eclipse_language]     More? (;) 
1357
1358X = locked
1359Y = off
1360yes.
1361",
1362	see_also:[(import)/1, (export)/1, (reexport)/1,
1363		document:icompile/1, document:icompile/2,
1364		lock/0, lock_pass/1, unlock/2]]).
1365
1366