Next: ref-mod-sum, Previous: ref-mod-met, Up: ref-mod [Contents][Index]
Although module name expansion is performed when code is consulted, compiled or asserted,
it is perhaps best explained in terms of an interpreter,
especially the issue of how deeply clauses are expanded.
The semantics of call/1, taking meta_predicate
declarations into account, is shown as if defined by the interpreter
shown below.  The interpreter’s case analysis is as follows:
(Including cuts and module prefixes). The interpreter implements the semantics of the construct, expanding its argument.
First, we look for a meta_predicate declaration for N/A.
If one exists, then the relevant arguments are expanded.
Otherwise, the goal is left unexpanded.
Then, if N/A is a built-in predicate, then it is called.
Otherwise, a clause with head functor N/A is looked up
using the imaginary predicate :-/2,
unified against, and its body is interpreted.
Raise error exception.
Throughout the interpretation, we must keep track of the module context.
The interpreter is as follows, slightly simplified.
-->/2 is not a predicate:
call(M:Body) :-
        icall(Body, M).
icall(Var, M) :- \+callable(Var), !,
        must_be(Var, callable, call(M:Var), 1).
icall(M:Body, _) :- !,
        icall(Body, M).
icall(!, _) :- !,
        % cut relevant choicepoints.
icall((A, B), M) :- !,
        icall(A, M),
        icall(B, M).
icall((A -> B), M) :- !,
    (   icall(A, M) ->
        icall(B, M)
    ).
icall((A -> B ; C), M) :- !,
    (   icall(A, M) ->
        icall(B, M)
    ;   icall(C, M)
    ).
icall((A ; B), M) :- !,
    (   icall(A, M)
    ;   icall(B, M)
    ).
icall(\+(A), M) :- !,
    (   icall(A, M) ->
        fail
    ;   true
    ).
icall(_^A, M) :- !,
        icall(A, M).
icall(do(Iter,Body), M) :- !,
    (   Iter,
        param(M)
    do  icall(Body, M)
    ).
icall(if(A,B,C), M) :- !,
     if(icall(A, M),
        icall(B, M),
        icall(C, M)).
icall(once(A), M) :- !,
    (   icall(A, M) -> true
    ).
icall(Goal, M) :-
    (   predicate_property(M:Goal, meta_predicate(Meta)) ->
        functor(Goal, Name, Arity),
        functor(AGoal, Name, Arity),
        (   foreacharg(Spec,Meta),
            foreacharg(Arg,Goal),
            foreacharg(Ann,AGoal),
            param(M)
        do  (   Spec==(:) -> Ann = M:Arg
            ;   integer(Spec) -> Ann = M:Arg
            ;   Ann = Arg
            )
        ),
        call_goal(AGoal, M)
    ;   call_goal(Goal, M)
    ).
call_goal(asserta(X), M) :- !,
        asserta(M:X).
call_goal(asserta(X,R), M) :- !,
        asserta(M:X, R).
% and so on for all built-in predicates
call_goal(Goal, M) :-
        (M:Goal :- Body),
        icall(Body, M).