Prolog and Erlang have many similarities. For historic reasons, the syntax of Erlang is very close to the syntax of Prolog. Both of them have a "flat" module system where a module is a chunk of code named by an atom, which may import routines from other modules and export routines to any module that is interested.
Neither Prolog nor Erlang has any "structured" kind of unit that is smaller than a module file. If you want to compose a module from smaller pieces, you use an "include" directive.
If F is an implementation-defined ground term designating a Prolog text unit, then Prolog text P1 which contains a directiveinclude(F)
is identical to a Prolog text P2 obtained by replacing the directiveinclude(F)
in P1 by the Prolog text denoted by F.
This is typical standardese (more precisely, typical ISO Prolog standardese) for
if a top level form is :- include(F).
,
where F is a file name, your Prolog system will act as
though the top level forms inside that file appeared in place of
the :-include directive.
In the formal version: "the Prolog text denoted
by F" should be "the Prolog text contained in the text unit
designated by F". Above all, the standard text suggests
that the contents of the file just replace the
include(F)
part, leaving the :-
and the full stop stranded just so they can cause trouble.
Include directives are mainly useful so that operator declarations can be shared by several modules; anything else can be imported as normal code.
The same syntax as for module attributes is used for file inclusion:-include(File). -include_lib(File).
File
, a string, should point out a file. The contents of this file are included as-is, at the position of the directive.Include files are typically used for record and macro definitions that are shared by several modules. It is recommended that the file name extension
.hrl
be used for include files.
File
may start with a path component$VAR
, for some string name$VAR
. If that is the case, the value of the environment variableVAR
as returned byos:getenv(VAR)
is substituted for$VAR
. Ifos:getenv(VAR)
returnsfalse
,$VAR
is left as is.If the file name
File
is absolute (possibly after variable substitution), the include file with that name is included. Otherwise, the specified file is searched for in the current working directory, in the same directory as the module being compiled, and in the directories given by theinclude
option, in that order. Seeerlc(1)
andcompile(3)
for details.Examples:
-include("my_records.hrl"). -include("incdir/my_records.hrl"). -include("/home/user/proj/my_records.hrl"). -include(""$PROJ_ROOT/my_records.hrl").
include_lib
is similar toinclude
, but should not point out an absolute file. Instead, the first path component (possibly after variable substitution) is assumed to be the name of an application. Example:-include_lib("kernel/include/file.hrl").The code server uses
code:lib_dir(kernel)
to find the directory of the current (latest) version of Kernel, and then the subdirectoryinclude
is searched for the filefile.hrl
Erlang's include_lib
is not as big an addition to
Prolog's include
as it looks; Prolog systems commonly
allow structured file names that do the same job more generally.
:-include
or -include
directive has no way
whatever of telling what the included file needs from its includer
or what it provides to its includer, other than going and looking.
-ifdef(use_ping). -include("ping.hrl"). -else. -include("pong.hrl"). -endif.
This is an issue for Prolog, because there is no standard or commonly accepted conditional compilation feature for Prolog, but it's also a problem for Erlang. In particular, you cannot "drop in" a new or experimental version of an inclusion without changing the module file.
I propose a solution in which
-module(Module_Name). ( -export(Exports). | -import(Other_Module_Name, Imports). | -compile(Options). | -vsn(Version). | -behaviour(Behaviour_Module_Name). | -Other_Tag(Term). )* ( Preprocessor directive. | -include(File_Name). | -include_lib(File_Name). | Out of line child | In line child | -Other_Tag(Term). | Function definition. )+
The only change here is the addition of Out of line child and In line child.
-use_child(Child_Name, From_The_Child[, To_The_Child[, integrated | replaceable]]).
From_The_Child is like an -import
directive;
it says that the child module is required to provide the listed
functions. Those functions will be available in the parent
without any module qualification; a child module is not a full
module and module qualification applies only to things imported from
full modules.
For any module or child module X, the From_The_Child lists of all its children must be disjoint, and none of them may mention anything defined in X proper. Not may a From_The_Child list have any element in common with the To_The_Child list for the same child. However, "cyclic" dependencies between children are allowed. Example:
:- use_child(fred, [roast/1], [beef/2]). :- use_child(mary, [beef/2], [roast/1]).
To_The_Child is like an -export
directive;
it says that the child module is allowed to use the listed functions
visible in the parent, and those only. If To_The_Child is
omitted, it is taken to be an empty list. Note that a child module
is allowed to import functions from full modules, and that includes
its own ancestor.
The integrated
option says that the child is to be
bound early with the parent. The interface specification controls
visibility, but the compiler may consider the module together with
all its integrated children (and their integrated children, transitively)
as a single unit and do whatever type inference, inlining, or other
optimisation it wishes. The replaceable
options says that
the child is to be bound late with the parent. Whatever code is
generated must allow the child to be replaced at run time.
The default is integrated
.
-begin_child(Child_Name, From_The_Child[, To_The_Child). ( -import(Other_Module_Name, Imports). | -vsn(Version). | -Other_Tag(Term). )* ( Preprocessor directive. | -include(File_Name). | -include_lib(File_Name). | Out of line child | In line child | -Other_Tag(Term). | Function definition. )+ -end_child(Child_Name).
The preprocessor ?MODULE
hack remains available in the
proper body of a full module. It is not available in any child
module, whether in line or out of line. You are supposed to be able to
understand most things of importance for understanding a child module
just by looking at it. Even an in line child may have been
-include
d, so a child module might be shared by any number
of modules in which case you don't know what ?MODULE
means.
In particular, code like
-child(fred, [f/0]). f() -> f(?MODULE). f(mummy) -> true; f(daddy) -> false.
can be done with plain -include
, but intentionally
cannot be written using child modules of any kind.
A child module may not -export
anything. The closest it
can come is to provide features to its parent.
In contrast, a child module may -import
from other (full)
modules. Functions imported from other modules cannot be provided to the
parent, only functions defined in the child or available in it from
children of its own. The scope of an -import
directive in
an In line child is limited to that child. Conversely, an
-import
directive in a parent has no effect on its children.
The idea is that you should be able to take an out of line child and move
it in line, or an in line child and move it out of line, without any
change to its body. There is one exception, discussed next.
An in line child may not contain a -compile
directive;
the compiler options that apply to an integrated child are the same
as those that apply to its parent. An out of line child may contain
such directives.
An in line child may contain a -vsn
directive of its own;
it's not clear to me what should be done about such version information,
but it may be useful documentation.
A child module may not contain a -behaviour
directive.
Only a full module may be an instance of a behaviour.
The body of a child module is just like the body of a full module.
An in line child is closed by an -end_child
directive;
the Child_Name is repeated for readability and must match
the Child_Name in the corresponding -begin_child
.
-child(Child_Name, From_The_Child[, To_The_Child]). ( -import(Other_Module_Name, Imports). | -compile(Options). | -vsn(Version). | -Other_Tag(Term). )* ( Preprocessor directive. | -include(File_Name). | -include_lib(File_Name). | Out of line child | In line child | -Other_Tag(Term). | Function definition. )+
[ functor (, functor)* ]
An export list is a non-empty list of functors, where a functor is either name/arity, referring to an ordinary function, or #name/arity, referring to an abstract pattern. There is no point in an empty export list, so it isn't allowed.
[ (functor (, functor)*)? ]
An import list is a possibly empty list of functors. An empty import list can be useful to state a dependency on another module without allowing the abbreviation of any function names, so it is allowed.
[ item (, item)* ]
This is a non-empty list of items, where an item is either a functor or #record_name. Records may only be required of or provided to an integrated child (either in line or out of line). Long term, abstract patterns are envisaged as the replacement for records. Restricting record items to integrated children means that there is no need to mention anything more than the record name. Mentioning the record name means that it is obvious to a maintenance programmer which children what records come from.
[ (item (, item)*)? ]
The list of things provided to a child is a possibly empty list of items. Records may only be provided to an integrated child (either in line or out of line).
-module(demo). -export([f/0]). -use_child(shared_stuff, [k/1, #r]). f() -> k(#r{x=1}). % Eof -child(shared_stuff, [k/1, #r]). -record(r, {x=0}). k(#r{x=0}) -> 137; k(#r{x=1}) -> 42. % Eof -module(listy). -export([length/1, reverse/1]). -begin_child(length, [length/1]). length(Xs) -> length(Xs, 0). length([_|Xs], N) -> length(Xs, N+1); length([], N) -> N. -end_child(length). -begin_child(reverse, [reverse/1]). reverse(Xs) -> reverse(Xs, []). reverse([X|Xs], Ys) -> reverse(Xs, [X|Ys]); reverse([], Ys) -> Ys. -end_child(reverse). % Eof
The Prolog version is very much a draft.
:- child(Child_Name, From_The_Child[, To_The_Child]). :- use_child(Child_Name, From_The_Child[, To_The_Child[, integrated | replaceable]]). :- begin_child(Child_Name, From_The_Child[, To_The_Child[, integrated | replaceable]]). :- end_child(Child_Name).
:- module(demo, [f/1]). :- use_child(shared_stuff, [k/2]). f(X) :- k(r(1), X). % Eof :- child(shared_stuff, [k/2]). k(r(U), V) :- k_aux(U, V). k_aux(0, 137). k_aux(1, 42). % Eof :- module(listy, [length/2, reverse/2]). :- begin_child(length, [length/2]). length(Xs, N) :- length(Xs, 0, N). length([], N, N). length([_|Xs], N0, N) :- N1 is 1 + N0, length(Xs, N1, N). :- end_child(length). :- begin_child(reverse, [reverse/2]). reverse(Xs, Ys) :- reverse(Xs, [], Ys). reverse([], Ys, Zs). reverse([X|Xs], Ys0, Ys) :- reverse(Xs, [X|Ys0], Ys). :- end_child(reverse). % Eof
The predicate names child/[2,3]
are too useful to take away
from programmers, so :- child
is only interpreted as a child
module header when it is the very first directive in a file.
This is a very preliminary draft, and is more intended as something to get the idea across than as anything approximating a serious proposal.
The configuration language has two primary tasks:
SGML catalogues are a good analogy for what we are trying to do here. The official specification is SGML Open Technical Resolution TR401:1997. There is now an XML equivalent, with all the readability disadvantages of XML. James Clark has an explanation of the SGML version. Some of the entries that can occur in a catalogue are:
The simplest possible scheme for our purposes would be a simple list of {module name, file name} pairs, with all conditional processing done by some other means, such as M4. This could work, but M4 is Turing-complete, and it would be nice to have something simpler.
configuration = (inclusion | var-def | search-def)* default? module-def* inclusion = "<" file-name var-def = uc-identifier ( "|" guard "=" expression )+ | uc-identifier "=" expression guard = guard "&&" guard | guard "||" guard | "~" guard | "(" guard ")" | expression relop expression expression = expression "+" expression | expression "-" expression | "(" expression ")" | lc-identifier | number | uc-identifier search-def = "$" uc-identifier ( "|" guard "=" search-list )+ | "$" uc-identifier "=" search-list search-list = (search-list ",")? file-name file-name = "/"? file-part ("/" file-part)* ("(" file-part ")")? file-part = regular-file-part "." simple-file-part | regular-file-part regular-file-part = (regular-file-part "++")? (simple-file-part | "*") simple-file-part = lc-identifier | uc-identifier | "$" uc-identifier | string default = "*" = search-list module-def = lc-identifier ( "|" guard "=" module-rhs )+ | lc-identifier "=" module-rhs module-rhs = search-list children? | children children = "{" search-def* default child-def* "}" | "{" search-def* child-def+ "}" child-def = child-name ( "|" guard "=" child-rhs )+ | child-name child-name = ("." (lc-identifier | uc-identifier))+ child-rhs = module-rhs
A file-part may only contain a "*" if it is in the search list of a default. A default rule says that unless overridden by a later rule, a module is to be sought by substituting its name for the "*" in the search list.
A module-rhs may omit the search-list only when there is a default; an omitted search-list means to use the default fule.
Example:
$STDLIB = lib/stdlib/src $ERL = erl lists = $STDLIB/lists.$ERL { $LISTS = $STDLIB/lists.d .deprecated = $LISTS/old_stuff.$ERL .sorting = $LISTS/sorting .$ERL } ...
Example with defaults:
$STDLIB = lib/stdlib/src $ERL = erl * = $STDLIB/*.$ERL lists = { $LISTS = $STDLIB/lists.d * = $LISTS/*.$ERL .deprecated = $LISTS/old_stuff.$ERL % .sorting is handled by the inner default } % sets is handled by the outer default ...
Basically, a configuration file is a back-to-front lazy functional program, because there are no mutable data structures. Lazy, because nothing is evaluated until it is needed. Evaluation is driven by first processing the tops of all the module declarations, and then looking up the children of those modules as they are demanded by the compiler. Back-to-front, because the usual approach in functional languages is that the first declaration wins, while here the last rule to match any need is used. This ordering is chosen so that inclusions, going at the front, can be over-ridden by later definitions.
File names use slashes, but those slashes are operators, not literal text. Whether they map to "/", to "\", to ":", or even whether /a/b/c maps to [a.b]c, is system-dependent. In the same way, "." precedes an "extension" (also known as a file type), and whether that maps to "." or to ";" or to something else is system-dependent. Code may be kept in plain or compressed archives (Unix ".a", ".zip", ".jar", and so on, or MVS partitioned data sets), and the "(" ")" part of a file name refers to selecting a member from such a file. For example, we might have
$MYLIB = lib/otago/raok.zip * = $MYLIB(*)
Identifiers in simple-file-parts beginning with a lower case letter are literal text. Identifiers beginning with an upper case letter are meant for "wild-card" child module matching. Identifiers preceded by a $ sign are path names.
Conditional selection uses Haskell syntax.
An inclusion says to simply copy all the definitions in the included file.