View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        R.A. O'Keefe, V.S. Costa, L. Damas, Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2011-2016, Universidade do Porto, University of Amsterdam,
    7                              VU University Amsterdam.
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(random,
   37          [ random/1,                   % -Float (0,1)
   38            random_between/3,           % +Low, +High, -Random
   39
   40            getrand/1,                  % -State
   41            setrand/1,                  % +State
   42
   43            maybe/0,
   44            maybe/1,                    % +P
   45            maybe/2,                    % +K, +N
   46
   47            random_perm2/4,             % A,B, X,Y
   48
   49            random_member/2,            % -Element, +List
   50            random_select/3,            % ?Element, +List, -Rest
   51            random_subseq/3,            % ?List, ?Subseq, ?Complement
   52
   53            randseq/3,                  % +Size, +Max, -Set
   54            randset/3,                  % +Size, +Max, -List
   55            random_permutation/2,       % ?List, ?Permutation
   56            random_numlist/4,           % +P, +L, +U, -List
   57
   58                                        % deprecated interface
   59            random/3                    % +Low, +High, -Random
   60          ]).   61:- autoload(library(apply),[maplist/2]).   62:- autoload(library(error),
   63	    [must_be/2,domain_error/2,instantiation_error/1]).   64:- autoload(library(lists),[nth0/3,nth0/4,append/3]).   65:- autoload(library(pairs),[pairs_values/2]).

Random numbers

This library is derived from the DEC10 library random. Later, the core random generator was moved to C. The current version uses the SWI-Prolog arithmetic functions to realise this library. These functions are based on the GMP library.

author
- R.A. O'Keefe, V.S. Costa, L. Damas, Jan Wielemaker
See also
- Built-in function random/1: A is random(10) */
   79check_gmp :-
   80    current_arithmetic_function(random_float),
   81    !.
   82check_gmp :-
   83    print_message(warning, random(no_gmp)).
   84
   85:- initialization check_gmp.   86
   87
   88                 /*******************************
   89                 *         PRIMITIVES           *
   90                 *******************************/
 random(-R:float) is det
Binds R to a new random float in the open interval (0.0,1.0).
See also
- setrand/1, getrand/1 may be used to fetch/set the state.
- In SWI-Prolog, random/1 is implemented by the function random_float/0.
  100random(R) :-
  101    R is random_float.
 random_between(+L:int, +U:int, -R:int) is semidet
Binds R to a random integer in [L,U] (i.e., including both L and U). Fails silently if U<L.
  108random_between(L, U, R) :-
  109    integer(L), integer(U),
  110    !,
  111    U >= L,
  112    R is L+random((U+1)-L).
  113random_between(L, U, _) :-
  114    must_be(integer, L),
  115    must_be(integer, U).
 random(+L:int, +U:int, -R:int) is det
random(+L:float, +U:float, -R:float) is det
Generate a random integer or float in a range. If L and U are both integers, R is a random integer in the half open interval [L,U). If L and U are both floats, R is a float in the open interval (L,U).
deprecated
- Please use random/1 for generating a random float and random_between/3 for generating a random integer. Note that random_between/3 includes the upper bound, while this predicate excludes it.
  131random(L, U, R) :-
  132    integer(L), integer(U),
  133    !,
  134    R is L+random(U-L).
  135random(L, U, R) :-
  136    number(L), number(U),
  137    !,
  138    R is L+((U-L)*random_float).
  139random(L, U, _) :-
  140    must_be(number, L),
  141    must_be(number, U).
  142
  143
  144                 /*******************************
  145                 *             STATE            *
  146                 *******************************/
 setrand(+State) is det
 getrand(-State) is det
Query/set the state of the random generator. This is intended for restarting the generator at a known state only. The predicate setrand/1 accepts an opaque term returned by getrand/1. This term may be asserted, written and read. The application may not make other assumptions about this term.

For compatibility reasons with older versions of this library, setrand/1 also accepts a term rand(A,B,C), where A, B and C are integers in the range 1..30,000. This argument is used to seed the random generator. Deprecated.

Errors
- existence_error(random_state, _) is raised if the underlying infrastructure cannot fetch the random state. This is currently the case if SWI-Prolog is not compiled with the GMP library.
See also
- set_random/1 and random_property/1 provide the SWI-Prolog native implementation.
  169setrand(rand(A,B,C)) :-
  170    !,
  171    Seed is A<<30+B<<15+C,
  172    set_random(seed(Seed)).
  173setrand(State) :-
  174    set_random(state(State)).
  175
  176:- if(current_predicate(random_property/1)).  177getrand(State) :-
  178    random_property(state(State)).
  179:- else.  180getrand(State) :-
  181    existence_error(random_state, State).
  182:- endif.  183
  184
  185                 /*******************************
  186                 *            MAYBE             *
  187                 *******************************/
 maybe is semidet
Succeed/fail with equal probability (variant of maybe/1).
  193maybe :-
  194    random(2) =:= 0.
 maybe(+P) is semidet
Succeed with probability P, fail with probability 1-P
  200maybe(P) :-
  201    must_be(between(0.0,1.0), P),
  202    random_float < P.
 maybe(+K, +N) is semidet
Succeed with probability K/N (variant of maybe/1)
  208maybe(K, N) :-
  209    integer(K), integer(N),
  210    between(0, N, K),
  211    !,
  212    random(N) < K.
  213maybe(K, N) :-
  214    must_be(nonneg, K),
  215    must_be(nonneg, N),
  216    domain_error(not_less_than_zero,N-K).
  217
  218
  219                 /*******************************
  220                 *          PERMUTATION         *
  221                 *******************************/
 random_perm2(?A, ?B, ?X, ?Y) is semidet
Does X=A,Y=B or X=B,Y=A with equal probability.
  227random_perm2(A,B, X,Y) :-
  228    (   maybe
  229    ->  X = A, Y = B
  230    ;   X = B, Y = A
  231    ).
  232
  233
  234                 /*******************************
  235                 *    SET AND LIST OPERATIONS   *
  236                 *******************************/
 random_member(-X, +List:list) is semidet
X is a random member of List. Equivalent to random_between(1, |List|), followed by nth1/3. Fails of List is the empty list.
Compatibility
- Quintus and SICStus libraries.
  245random_member(X, List) :-
  246    must_be(list, List),
  247    length(List, Len),
  248    Len > 0,
  249    N is random(Len),
  250    nth0(N, List, X).
 random_select(-X, +List, -Rest) is semidet
random_select(+X, -List, +Rest) is det
Randomly select or insert an element. Either List or Rest must be a list. Fails if List is the empty list.
Compatibility
- Quintus and SICStus libraries.
  260random_select(X, List, Rest) :-
  261    (   '$skip_list'(Len, List, Tail),
  262        Tail == []
  263    ->  true
  264    ;   '$skip_list'(RLen, Rest, Tail),
  265        Tail == []
  266    ->  Len is RLen+1
  267    ),
  268    !,
  269    Len > 0,
  270    N is random(Len),
  271    nth0(N, List, X, Rest).
  272random_select(_, List, Rest) :-
  273    partial_list(List), partial_list(Rest),
  274    instantiation_error(List+Rest).
  275random_select(_, List, Rest) :-
  276    must_be(list, List),
  277    must_be(list, Rest).
 random_subseq(+List, -Subseq, -Complement) is det
random_subseq(-List, +Subseq, +Complement) is semidet
Selects a random subsequence Subseq of List, with Complement containing all elements of List that were not selected. Each element of List is included with equal probability in either Subseq or Complement.

random_subseq/3 may also be called with Subseq and Complement bound and List unbound, which will recreate List by randomly interleaving Subseq and Complement. This mode may fail randomly, matching SICStus behavior. The failure probability corresponds to the probability of the "forward" mode selecting a Subseq/Complement combination with different lengths.

Compatibility
- SICStus 4
  296random_subseq([], [], []).
  297random_subseq([Head|Tail], Subseq, Complement) :-
  298    (   maybe
  299    ->  Subseq = [Head|SubTail],
  300        Complement = CompTail
  301    ;   Subseq = SubTail,
  302        Complement = [Head|CompTail]
  303    ),
  304    random_subseq(Tail, SubTail, CompTail).
 randset(+K:int, +N:int, -S:list(int)) is det
S is a sorted list of K unique random integers in the range 1..N. The implementation uses different techniques depending on the ratio K/N. For small K/N it generates a set of K random numbers, removes the duplicates and adds more numbers until |S| is K. For a large K/N it enumerates 1..N and decides randomly to include the number or not. For example:
?- randset(5, 5, S).
S = [1, 2, 3, 4, 5].          (always)
?- randset(5, 20, S).
S = [2, 7, 10, 19, 20].
See also
- randseq/3.
  324randset(K, N, S) :-
  325    must_be(nonneg, K),
  326    K =< N,
  327    (   K < N//7
  328    ->  randsetn(K, N, [], S)
  329    ;   randset(K, N, [], S)
  330    ).
  331
  332randset(0, _, S, S) :- !.
  333randset(K, N, Si, So) :-
  334    random(N) < K,
  335    !,
  336    J is K-1,
  337    M is N-1,
  338    randset(J, M, [N|Si], So).
  339randset(K, N, Si, So) :-
  340    M is N-1,
  341    randset(K, M, Si, So).
  342
  343randsetn(K, N, Sofar, S) :-
  344    length(Sofar, Len),
  345    (   Len =:= K
  346    ->  S = Sofar
  347    ;   Needed is K-Len,
  348        length(New, Needed),
  349        maplist(srand(N), New),
  350        (   Sofar == []
  351        ->  sort(New, Sorted)
  352        ;   append(New, Sofar, Sofar2),
  353            sort(Sofar2, Sorted)
  354        ),
  355        randsetn(K, N, Sorted, S)
  356    ).
  357
  358srand(N, E) :-
  359    E is random(N)+1.
 randseq(+K:int, +N:int, -List:list(int)) is det
S is a list of K unique random integers in the range 1..N. The order is random. Defined as
randseq(K, N, List) :-
      randset(K, N, Set),
      random_permutation(Set, List).
See also
- randset/3.
  374randseq(K, N, Seq) :-
  375    randset(K, N, Set),
  376    random_permutation_(Set, Seq).
 random_permutation(+List, -Permutation) is det
random_permutation(-List, +Permutation) is det
Permutation is a random permutation of List. This is intended to process the elements of List in random order. The predicate is symmetric.
Errors
- instantiation_error, type_error(list, _).
  387random_permutation(List1, List2) :-
  388    is_list(List1),
  389    !,
  390    random_permutation_(List1, List2).
  391random_permutation(List1, List2) :-
  392    is_list(List2),
  393    !,
  394    random_permutation_(List2, List1).
  395random_permutation(List1, List2) :-
  396    partial_list(List1), partial_list(List2),
  397    !,
  398    instantiation_error(List1+List2).
  399random_permutation(List1, List2) :-
  400    must_be(list, List1),
  401    must_be(list, List2).
  402
  403random_permutation_(List, RandomPermutation) :-
  404    key_random(List, Keyed),
  405    keysort(Keyed, Sorted),
  406    pairs_values(Sorted, RandomPermutation).
  407
  408key_random([], []).
  409key_random([H|T0], [K-H|T]) :-
  410    random(K),
  411    key_random(T0, T).
 random_numlist(+P, +L, +U, -List) is det
Unify List with an ascending list of integers between L and U (inclusive). Each integer in the range L..U is included with probability P.
Compatibility
- SICStus 4
  421random_numlist(P, L, U, List) :-
  422    must_be(between(0.0, 1.0), P),
  423    must_be(integer, L),
  424    must_be(integer, U),
  425    random_numlist_(P, L, U, List).
  426random_numlist_(_P, L, U, List) :-
  427    L > U,
  428    !,
  429    List = [].
  430random_numlist_(P, L, U, List) :-
  431    (   maybe(P)
  432    ->  List = [L|Tail]
  433    ;   List = Tail
  434    ),
  435    L1 is L + 1,
  436    random_numlist_(P, L1, U, Tail).
 partial_list(@Term) is semidet
True if Term is a partial list.
  442partial_list(List) :-
  443    '$skip_list'(_, List, Tail),
  444    var(Tail).
  445
  446:- multifile
  447    prolog:message//1.  448
  449prolog:message(random(no_gmp)) -->
  450    [ 'This version of SWI-Prolog is not compiled with GMP support.'-[], nl,
  451      'Floating point random operations are not supported.'-[]
  452    ]