1:- module(interpolate, ['$interpolate_macro_sentinel'/0]).    2:- use_module(library(dcg/basics), [prolog_var_name//1, string//1]).    3:- use_module(library(function_expansion)).    4:- use_module(library(error), [type_error/2]).
Parse a list of codes as if it were an interpolated string. Formats is a list of atoms that can be joined together to create the first argument of format/2. Args are values for the second.
   12template(Vars, [Static,_|Formats], [Arg|Args]) -->
   13    string(Codes),
   14    variable(VarName),
   15    { memberchk(VarName=Arg, Vars) },
   16    { atom_codes(Static, Codes) },
   17    template(Vars, Formats, Args).
   18template(_, [Format], []) -->
   19    string(Codes),
   20    { atom_codes(Format, Codes) }.
 variable(-VarName:atom)//
Parse a $-prefixed variable name. Like $Message. For now this is a thin wrapper around prolog_var_name//1 but may eventuall grow to support other kinds of variables so I want the details abstracted away.
   29variable(VarName) -->
   30    "$",
   31    prolog_var_name(VarName).
   32
   33
   34% true if the module whose terms are being read has specifically
   35% requested string interpolation.
   36wants_interpolation :-
   37    prolog_load_context(module, Module),
   38    Module \== interpolate,  % we don't want string interpolation ourselves
   39    predicate_property(
   40        Module:'$interpolate_macro_sentinel',
   41        imported_from(interpolate)
   42    ).
 textual(-Type:atom, +Text, -Codes)
True if Text is of type Type and representable as Codes.
   48textual(_,Var,_) :-
   49    var(Var),
   50    !,
   51    fail.
   52textual(atom, Atom, Codes) :-
   53    atom(Atom),
   54    !,
   55    atom_codes(Atom,Codes).
   56textual(Type, Text, Codes) :-
   57    is_list(Text),
   58    !,
   59    Text = [H|_],  % empty lists are not text for our purposes
   60    ( atom(H) ->
   61        Type = chars,
   62        catch(atom_chars(Atom,Text),_,fail),
   63        atom_codes(Atom,Codes)
   64    ; integer(H) ->
   65        Type = codes,
   66        Codes = Text
   67    ).  % fail on all other lists
   68textual(string, String, Codes) :-
   69    string(String),
   70    string_to_list(String,Codes).
 build_text(?Output, ?Formats:list, ?Args:list)
Like format/3 but dynamically chooses tilde sequences to match the values in Args.
   77build_text(Output, Formats0, Args) :-
   78    instantiate_formats(Formats0, Args, Formats),
   79    atomic_list_concat(Formats, Format),
   80    format(Output, Format, Args).
   81
   82
   83% choose format tilde sequences for a list of values
   84instantiate_formats([], _, []).
   85instantiate_formats([Static|Formats0],Args,[Static|Formats]) :-
   86    atom(Static),
   87    !,
   88    instantiate_formats(Formats0,Args,Formats).
   89instantiate_formats([Var|Formats0],[Arg|Args],[Format|Formats]) :-
   90    var(Var),
   91    !,
   92    preferred_tilde(Arg,Format),
   93    instantiate_formats(Formats0,Args,Formats).
   94instantiate_formats([X|_],_,[_|_]) :-
   95    type_error(atom_or_var,X).
   96
   97
   98% Which format/2 tilde sequence does a value prefer?
   99preferred_tilde(X,'~s') :-
  100    textual(Type, X, _),
  101    ( Type = codes; Type = chars; Type = string ),
  102    !.
  103preferred_tilde(_,'~p').
  104
  105
  106:- multifile user:function_expansion/3.  107user:function_expansion(Term,Replacement,Guard) :-
  108    wants_interpolation,
  109    prolog_load_context(variable_names, Vars),
  110    Vars \== [],  % need variables to interpolate
  111
  112    % is this a string in need of interpolation?
  113    textual(Type, Term, TextCodes),
  114    phrase(template(Vars, Formats, Args), TextCodes),
  115    Args \== [],  % no args means no interpolation
  116
  117    % yup, so perform the expansion
  118    Output =.. [Type, Replacement],
  119    Guard = interpolate:build_text(Output, Formats, Args).
 $interpolate_macro_sentinel
Nothing to see here. This is an implementation detail to avoid unwanted string interpolation. Because string interpolation is implemented as a macro and macro expansion is done through a predicate with gloabl reach (term_expansion/2), we must take precautions to avoid performing string interpolation on code that doesn't want it. Importing this predicate opts-in to string interpolation. Writing use_module(library(interpolate)) does it for you.
  132'$interpolate_macro_sentinel'