Did you know ... Search Documentation:
Pack sweet -- prolog/sweet.pl
PublicShow source
 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.

 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.
 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.

 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:
  • list - X is an element of the list
  • dict - X is Key-Val pair for each entry
  • library(assoc) - X is Key-Val pair for each entry
  • library(rbtrees) - X is Key-Val pair for each entry

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.

 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]).

 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.

 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.
 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])
)
 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.