1:- module(sweet, [ cleanup/1
    2                 , if/2
    3                 , if/3
    4                 , in/2
    5                 , otherwise/0
    6                 , todo/0
    7                 , todo/1
    8                 , todo/2
    9                 , (use)/1
   10                 , op(990,xfy,in)
   11                 , op(1150,fx,use)
   12                 ]).   13
   14:- use_module(library(apply), [maplist/3]).   15:- use_module(library(error), [must_be/2]).   16:- use_module(library(lambda)).   17
   18
   19% true if module being loaded wants our macros expanded
   20wants_sweetner :-
   21    prolog_load_context(module, Module),
   22    Module \== sweet, % don't sweeten ourselves
   23    current_predicate(Module:otherwise/0),  % prevent autoloading
   24    predicate_property(Module:otherwise,imported_from(sweet)).
 cleanup(:Goal) is det
Sugar for call_cleanup/2. It's like ignore(once(Goal)) but postponed until the clause is finished. The surrounding context provides the call goal. For example,
file_codes(File,Codes) :-
    open(File,read,Stream),
    cleanup(close(Stream)),
    read_stream_to_codes(Stream, Codes).

If a clause calls cleanup/1 multiple times, the cleanup steps are performed in LIFO order. If you need your code to be safe against asynchronous interrupts, use setup_call_cleanup/3 instead.

   41:- meta_predicate cleanup(1).   42cleanup(Goal) :-
   43    throw(sweet("cleanup/1 macro not expanded", Goal)).
   44
   45% cleanup_macro(+Goal:callable,-Rewritten:callable)
   46cleanup_macro(Old,New) :-
   47    cleanup_macro_(Old,New),
   48    Old \== New.
   49
   50cleanup_macro_(cleanup(Cleanup),Rewritten) :-
   51    % cleanup/1 as final goal in a clause
   52    !,
   53    Rewritten = ignore(once(Cleanup)).
   54cleanup_macro_((cleanup(Cleanup),Call0),Rewritten) :-
   55    % cleanup/1 with a goal after it (common case)
   56    !,
   57    cleanup_macro_(Call0,Call),
   58    Rewritten = call_cleanup(Call,Cleanup).
   59cleanup_macro_((A0,B0),Rewritten) :-
   60    % A0 \= cleanup(_)
   61    !,
   62    cleanup_macro_(A0,A),
   63    cleanup_macro_(B0,B),
   64    Rewritten = (A,B).
   65cleanup_macro_((A->B0;C0),Rewritten) :-
   66    !,
   67    cleanup_macro_(B0,B),
   68    cleanup_macro_(C0,C),
   69    Rewritten = (A->B;C).
   70cleanup_macro_((A*->B0;C0),Rewritten) :-
   71    !,
   72    cleanup_macro_(B0,B),
   73    cleanup_macro_(C0,C),
   74    Rewritten = (A*->B;C).
   75cleanup_macro_(Goal,Goal).
 if(:Condition, :Action)
Same as (Condition->Action;true). For historic reasons, the standard conditional predicate fails if the condition fails. In many circumstances, one would prefer a noop in that case.
   83:- meta_predicate if(0,0).   84if(Condition, Action) :-
   85    throw(sweet("if/2 macro not expanded",Condition,Action)).
 if(:Condition, :Action, :Else)
Same as (Condition->Action;Else). When modifying code that started with if/2, one often gets a cleaner "diff" by using if/3 instead of restructuring the whole code to use -> ;.

For example,

@@ -1,3 +1,4 @@
 if( thing
   , stuff
+  , other
   )

vs

@@ -1,3 +1,4 @@
-if( thing
-  , stuff
-  )
+( thing ->
+    stuff
+; other
+)

This is important for those who view commits as a means of communication between developers rather than just an artificat of version control tools.

  115:- meta_predicate if(0,0,0).  116if(Cond,Action,Else) :-
  117    throw(sweet("if/3 macro not expanded",Cond,Action,Else)).
 in(?X, +Xs)
True if X is contained in Xs. For convenience, in/2 is exported as an operator: X in [1,2,3]. Xs must be nonvar. The following types for Xs are supported natively:

In each case, if X or Key is ground, a lookup operation (or memberchk/2) is performed. If X or Key is unbound, each member of Xs is iterated on backtracking.

To add in/2 support for your own types, add a clause to the multifile predicate sweet:has_member(+Xs,?X). As soon as your clause is certain that Xs is of the right type, please call !/0. This keeps in/2 deterministic where possible.

  139in(X, Xs) :-
  140    must_be(nonvar, Xs),
  141    has_member(Xs, X).
  142
  143:- multifile has_member/2.  144has_member([H|T], X) :-
  145    !,
  146    ( var(X) ->
  147        ( T=[] ->
  148            X=H
  149        ; otherwise ->
  150            (X=H ; has_member(T,X) )
  151        )
  152    ; X=H ->
  153        true
  154    ; otherwise ->
  155        has_member(T, X)
  156    ).
  157has_member(Dict, X) :-
  158    is_dict(Dict),
  159    !,
  160    X = Key-Val,
  161    get_dict(Key,Dict,Val).
  162has_member(Assoc, X) :-
  163    current_predicate(assoc:is_assoc/1), % proceed if library(assoc) loaded
  164    assoc:is_assoc(Assoc),
  165    !,
  166    X = Key-Val,
  167    ( var(Key) ->
  168        assoc:gen_assoc(Key,Assoc,Val)
  169    ; X = Key-Val ->
  170        get_assoc(Key,Assoc,Val)
  171    ).
  172has_member(Rb, X) :-
  173    current_predicate(rbtrees:is_rbtree/1), % proceed if library(rbtrees) loaded
  174    rbtrees:is_rbtree(Rb),
  175    !,
  176    X = Key-Val,
  177    rbtrees:rb_in(Key,Val,Rb).
 otherwise is det
AKA true. This alias is helpful for maintaining visual similarity for the final clause of a chained if-then-else construct. For example:
( foo(X) ->
    do_foo_stuff
; bar(X) ->
    do_bar_stuff
; otherwise ->
    do_default_stuff
).

This predicate is identical to quintus:otherwise/0. It's included here for environments in which autoload is disabled and one doesn't want to add :- use_module(library(quintus), [otherwise/0]).

  197otherwise.
  198:- '$hide'(sweet:otherwise/0).
 todo
Throws the exception todo. This is convenient during rapid development to mark code that will be written later. If the predicate is accidentally executed, it throws an exception so you can view the stack trace, implement proper code and resume execution.

For exmaple,

( stuff ->
    handle_the_common_case
; otherwise ->
    todo
)

Using todo/0, todo/1 or todo/2 also provides a useful semantic distinction compared to throw/1. Static analysis tools might prevent commits or deployment for unfinished code.

  219todo :-
  220    throw(todo).
 todo(+Note)
Like todo/0 with a Note. Note can be used to leave yourself a reminder of what this code is supposed to do once it's implemented. If todo/1 is executed, it throws an exception.
  227todo(Explanation) :-
  228    throw(Explanation).
 todo(+Note, ?Extra)
Like todo/1 but provides space for something Extra. This is often a list of variables that will eventually participate in the code that's to be written. This style prevents singleton warnings during development. If todo/2 is executed, Extra is not included in the exception.

For example,

( stuff ->
    handle_the_common_case(X)
; otherwise ->
    todo("set a meaningful default", [X])
)
  246todo(Note,_Extra) :-
  247    throw(Note).
 use(+ModuleImportOptions)
Macros for importing modules. SWI Prolog's module system is powerful and well designed. Unfortunately, the syntax is highly repetitive in the common case (importing library predicates). The following macros simplify import declarations making them easier to read. Future releases will add some additional, optional power to the module system.

These macros are best understood through a series of examples. In each example, the first line shows the sweetened version. The following comment shows how the macro expands.

:- use random.
% :- use_module(library(random)).

:- use random -> random/1.
% :- use_module(library(random), [random/1]).

:- use lists -> append/{2,3}.
% :- use_module(library(lists), [append/2,append/3]).

:- use path(baz).
% :- use_module(path(baz)).
% path(baz) could be anything supported by file_search_path/2

:- use my(foo) -> bar/0.
% :- use_module(foo, [bar/0]).
% my/1 is an escape hatch to pass a term straight through to
% use_module.  Named "my" because it's typically used for
% accessing modules relative to the local directory.
  281use(Options) :-
  282    throw(sweet("use/1 macro not expanded", Options)).
  283
  284% translate our module spec into a use_module file term
  285spec_to_file(my(File),File) :-
  286    !.
  287spec_to_file(Module,library(Module)) :-
  288    atom(Module),
  289    !.
  290spec_to_file(Module,Module).
  291
  292% "foo/1,bar/2" into "[foo/1,bar/2]"
  293pred_conj_to_list((Pattern,Rest),AllIndicators) :-
  294    pred_pattern_to_list(Pattern,Indicators),
  295    append(Indicators,RestIndicators,AllIndicators),
  296    pred_conj_to_list(Rest,RestIndicators).
  297pred_conj_to_list(Pattern,Indicators) :-
  298    pred_pattern_to_list(Pattern,Indicators).
  299
  300% "foo/{2,3}" into "[foo/2,foo/3]"
  301pred_pattern_to_list(Name/Arity,[Name/Arity]) :-
  302    integer(Arity).
  303pred_pattern_to_list(Name/{ArityConj},Indicators) :-
  304    xfy_list(',',ArityConj,ArityList),
  305    maplist(\Arity^Indicator^(Indicator=Name/Arity),ArityList,Indicators).
  306
  307% copied from library(list_util) to avoid the dependency
  308xfy_list(Op, Term, [Left|List]) :-
  309    Term =.. [Op, Left, Right],
  310    xfy_list(Op, Right, List),
  311    !.
  312xfy_list(_, Term, [Term]).
  313
  314% define macro expansions as an easily testable predicate
  315macro(
  316  term,
  317  (:- use Spec -> PredicateConj),
  318  (:- use_module(File, PredicateList) )
  319) :-
  320    spec_to_file(Spec,File),
  321    pred_conj_to_list(PredicateConj,PredicateList).
  322macro(
  323  term,
  324  (:- use Spec),
  325  (:- use_module(File))
  326) :-
  327    spec_to_file(Spec,File).
  328macro(
  329  goal,
  330  if(Cond,Action),
  331  (Cond->Action;true)
  332).
  333macro(
  334  goal,
  335  if(Cond,Action,Else),
  336  (Cond->Action;Else)
  337).
  338
  339% expand use/1 macros
  340user:term_expansion(Old,New) :-
  341    wants_sweetner,
  342    macro(term,Old,New).
  343
  344% expand goal macros
  345user:goal_expansion(Old,New) :-
  346    wants_sweetner,
  347    macro(goal,Old,New).
  348
  349% expand cleanup/1 macros
  350user:term_expansion((Head:-Old),(Head:-New)) :-
  351    wants_sweetner,
  352    cleanup_macro(Old,New)