Did you know ... Search Documentation:
Pack spawn -- prolog/spawn.pl
PublicShow source
 spawn(:Goal) is det
Like spawn/2 with default options.
 spawn(:Goal, +Options) is det
Seek solutions to Goal in a background thread. Solutions are communicated to the calling thread by unifying free variables in Goal. If Goal has no free variables, you must use async/3 instead. Options are passed through to async/3.

For example, the following code runs in about 1 second because both sleep/1 calls happen in parallel. When foo/0 unifies L, it blocks until silly/1 has finished.

silly(L) :-
    sleep(1),
    L = [a,b].
foo :-
    spawn(silly(L)),
    sleep(1),
    L=[A,B],  % blocks, if necessary
    writeln(A-B).

If Goal produces multiple solutions, they're iterated when backtracking over the unification (L=[A,B] above). If Goal fails or throws an exception, the calling thread sees it at the unification point.

 lazy(Goal) is det
Postpone execution of goal until needed. This is just spawn/1 using the lazy thread policy.

lazy/1 can be helpful when complicated or expensive goals are only needed in some code paths but duplicating those goals is too verbose. It can be an alternative to creating a new, named predicate. For example,

foo(Xs) :-
    lazy(i_am_slow(a,B,[c(C),d(d),e(etc)])), % complicated

    ( day_of_week(tuesday) ->
        append(B,C,Xs)
    ; phase_of_moon(full) ->
        append(C,B,Xs)
    ; true ->
        % i_am_slow/3 not executed in this code path
        Xs = [hi]
    ).
 async(:Goal, -Token) is det
Like async/3 with default options.
 async(:Goal, -Token, +Options) is det
Seek solutions to Goal in a background thread. Use await/1 with Token to block until the computation is done. Solutions are communicated to the calling thread by unifying free variables in Goal. Both Goal and its corresponding solutions are copied between threads. Be aware if any of those terms are very large.

Options are as follows:

policy(Policy)
If ephemeral (default), create a new thread in which to call goal. If lazy, only execute Goal when await/1 is called; no background threads are used.
 await(+Token)
Wait for solutions from an async/3 call. Token is an opaque value provided by async/3 which identifies a background computation.

await/1 strives to have the same determinism as the original Goal passed to async/3. If that goal fails, await/1 fails. If that goal throws an exception, so does await/1. If that goal produces many solutions, so does await/1 on backtracking.