Did you know ... Search Documentation:
Pack func -- prolog/func.pl
PublicShow source
 compile_function(+Term, -In, -Out, -Goal) is semidet[multifile]
True if Term represents a function from In to Out implemented by calling Goal. This multifile hook is called by $/2 and of/2 to convert a term into a goal. It's used at compile time for macro expansion. It's used at run time to handle functions which aren't known at compile time. When called as a hook, Term is guaranteed to be nonvar.

For example, to treat library(assoc) terms as functions which map a key to a value, one might define:

:- multifile compile_function/4.
compile_function(Assoc, Key, Value, Goal) :-
    is_assoc(Assoc),
    Goal = get_assoc(Key, Assoc, Value).

Then one could write:

list_to_assoc([a-1, b-2, c-3], Assoc),
Two = Assoc $ b,
 $(+Function, +Argument) is det
Apply Function to an Argument. A Function is any predicate whose final argument generates output and whose penultimate argument accepts input.

This is realized by expanding function application to chained predicate calls at compile time. Function application itself can be chained.

Reversed = reverse $ sort $ [c,d,b].
 of(+F, +G) is det
Creates a new function by composing F and G. The functions are composed at compile time to create a new, compiled predicate which behaves like a function. Function composition can be chained. Composed functions can also be applied with $/2.
Reversed = reverse of sort $ [c,d,b].