1:- module(function_expansion, []).    2:- use_module(library(lists), [append/3]).    3:- use_module(library(apply), [exclude/3]).
 user:function_expansion(+Term, -Replacement, -Guard) is semidet
Like term_expansion/2, function_expansion/3 provides for macro expansion of Prolog source code. In this case, by expanding Term which is nested inside a parent term. Term is replaced with Replacement. Guard is placed as a conjunction before the parent term. Guard typically binds Replacement in some useful fashion.

For example, a function macro which doubles its argument might expand this

user:function_expansion(double(X), Y, Y is 2*X).
main :-
    V = 9,
    format('~p times 2 is ~p~n', [V, double(V)]).
into this

==
main :-
    V = 9,
    A is 2*V,
    format('~p times 2 is ~p~n', [V, A]).
==

Mathematical constants might be implemented like

==
user:function_expansion(pi, 3.14159, true).
==
   37:- dynamic user:function_expansion/3.   38:- multifile user:function_expansion/3.   39
   40expand_arglist([], [], []).
   41expand_arglist([H0|T0], [H|T], [Guard|Guards]) :-  % leaf
   42    nonvar(H0),
   43    user:function_expansion(H0, H, Guard),
   44    expand_arglist(T0, T, Guards),
   45    !.
   46expand_arglist([H0|T0], [H|T], Guards) :-          % subtree
   47    nonvar(H0),
   48    (compound(H0) -> compound_name_arguments(H0, Functor, Args0) ; H0 =.. [Functor|Args0]),
   49    expand_arglist(Args0, Args, NestedGuards),
   50    (compound(H0) -> compound_name_arguments(H, Functor, Args) ; H =.. [Functor|Args]),
   51    expand_arglist(T0, T, TailGuards),
   52    append(NestedGuards, TailGuards, Guards),
   53    !.
   54expand_arglist([H0|T0], [H0|T], Guards) :-
   55    var(H0),
   56    expand_arglist(T0, T, Guards).
 xfy_list(?Op:atom, ?Term, ?List) is det
True if List joined together with xfy operator Op gives Term. Usable in all directions. For example,
?- xfy_list(',', (a,b,c), L).
L = [a, b, c].
   67xfy_list(Op, Term, [Left|List]) :-
   68    Term =.. [Op, Left, Right],
   69    xfy_list(Op, Right, List),
   70    !.
   71xfy_list(_, Term, [Term]).
 control(+Term) is semidet
True if Term is a control structure such as =,=, =;=, etc.
   76control((_,_)).
   77control((_;_)).
   78control((_->_)).
   79control((_*->_)).
   80control(\+(_)).
   81
   82user:goal_expansion(T0, T) :-
   83    \+ control(T0),  % goal_expansion/2 already descends into these
   84    T0 =.. [Functor|Args],
   85    function_expansion:expand_arglist(Args, NewArgs, Preconditions),
   86    T1 =.. [Functor|NewArgs],
   87
   88    % remove guards that are always true
   89    exclude(==(true), Preconditions, NoTrues),
   90    (   xfy_list(',', Guard, NoTrues)
   91    ->  T = (Guard, T1)
   92    ;   T = T1   % empty guard clause
   93    ).
   94
   95user:term_expansion(H :- B, H1 :- (P, B)) :-
   96    H =.. Args,
   97    function_expansion:expand_arglist(Args, NewArgs, Preconditions),
   98    H1 =.. NewArgs,
   99    xfy_list(',', P, Preconditions)