View source with formatted 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
   52            randseq/3,                  % +Size, +Max, -Set
   53            randset/3,                  % +Size, +Max, -List
   54            random_permutation/2,       % ?List, ?Permutation
   55
   56                                        % deprecated interface
   57            random/3                    % +Low, +High, -Random
   58          ]).   59:- autoload(library(apply),[maplist/2]).   60:- autoload(library(error),
   61	    [must_be/2,domain_error/2,instantiation_error/1]).   62:- autoload(library(lists),[nth0/3,nth0/4,append/3]).   63:- autoload(library(pairs),[pairs_values/2]).   64
   65
   66/** <module> Random numbers
   67
   68This library is derived from the DEC10   library random. Later, the core
   69random generator was moved to C. The current version uses the SWI-Prolog
   70arithmetic functions to realise this library.  These functions are based
   71on the GMP library.
   72
   73@author         R.A. O'Keefe, V.S. Costa, L. Damas, Jan Wielemaker
   74@see            Built-in function random/1: A is random(10)
   75*/
   76
   77check_gmp :-
   78    current_arithmetic_function(random_float),
   79    !.
   80check_gmp :-
   81    print_message(warning, random(no_gmp)).
   82
   83:- initialization check_gmp.   84
   85
   86                 /*******************************
   87                 *         PRIMITIVES           *
   88                 *******************************/
   89
   90%!  random(-R:float) is det.
   91%
   92%   Binds R to a new random float in the _open_ interval (0.0,1.0).
   93%
   94%   @see setrand/1, getrand/1 may be used to fetch/set the state.
   95%   @see In SWI-Prolog, random/1 is implemented by the function
   96%        random_float/0.
   97
   98random(R) :-
   99    R is random_float.
  100
  101%!  random_between(+L:int, +U:int, -R:int) is semidet.
  102%
  103%   Binds R to a random integer in [L,U] (i.e., including both L and
  104%   U).  Fails silently if U<L.
  105
  106random_between(L, U, R) :-
  107    integer(L), integer(U),
  108    !,
  109    U >= L,
  110    R is L+random((U+1)-L).
  111random_between(L, U, _) :-
  112    must_be(integer, L),
  113    must_be(integer, U).
  114
  115
  116%!  random(+L:int, +U:int, -R:int) is det.
  117%!  random(+L:float, +U:float, -R:float) is det.
  118%
  119%   Generate a random integer or float in a   range.  If L and U are
  120%   both integers, R is a random integer   in the half open interval
  121%   [L,U). If L and U are both  floats,   R  is  a float in the open
  122%   interval (L,U).
  123%
  124%   @deprecated Please use random/1 for   generating  a random float
  125%   and random_between/3 for generating a  random integer. Note that
  126%   random_between/3  includes  the  upper  bound,  while  this
  127%   predicate excludes it.
  128
  129random(L, U, R) :-
  130    integer(L), integer(U),
  131    !,
  132    R is L+random(U-L).
  133random(L, U, R) :-
  134    number(L), number(U),
  135    !,
  136    R is L+((U-L)*random_float).
  137random(L, U, _) :-
  138    must_be(number, L),
  139    must_be(number, U).
  140
  141
  142                 /*******************************
  143                 *             STATE            *
  144                 *******************************/
  145
  146%!  setrand(+State) is det.
  147%!  getrand(-State) is det.
  148%
  149%   Query/set the state of the random   generator.  This is intended
  150%   for  restarting  the  generator  at  a  known  state  only.  The
  151%   predicate  setrand/1  accepts  an  opaque    term   returned  by
  152%   getrand/1. This term may be  asserted,   written  and  read. The
  153%   application may not make other assumptions about this term.
  154%
  155%   For compatibility reasons with older   versions of this library,
  156%   setrand/1 also accepts a term rand(A,B,C), where  A, B and C are
  157%   integers in the range 1..30,000. This   argument is used to seed
  158%   the random generator.  Deprecated.
  159%
  160%   @see    set_random/1 and random_property/1 provide the SWI-Prolog
  161%           native implementation.
  162%   @error  existence_error(random_state, _) is raised if the
  163%           underlying infrastructure cannot fetch the random state.
  164%           This is currently the case if SWI-Prolog is not compiled
  165%           with the GMP library.
  166
  167setrand(rand(A,B,C)) :-
  168    !,
  169    Seed is A<<30+B<<15+C,
  170    set_random(seed(Seed)).
  171setrand(State) :-
  172    set_random(state(State)).
  173
  174:- if(current_predicate(random_property/1)).  175getrand(State) :-
  176    random_property(state(State)).
  177:- else.  178getrand(State) :-
  179    existence_error(random_state, State).
  180:- endif.  181
  182
  183                 /*******************************
  184                 *            MAYBE             *
  185                 *******************************/
  186
  187%!  maybe is semidet.
  188%
  189%   Succeed/fail with equal probability (variant of maybe/1).
  190
  191maybe :-
  192    random(2) =:= 0.
  193
  194%!  maybe(+P) is semidet.
  195%
  196%   Succeed with probability P, fail with probability 1-P
  197
  198maybe(P) :-
  199    must_be(between(0.0,1.0), P),
  200    random_float < P.
  201
  202%!  maybe(+K, +N) is semidet.
  203%
  204%   Succeed with probability K/N (variant of maybe/1)
  205
  206maybe(K, N) :-
  207    integer(K), integer(N),
  208    between(0, N, K),
  209    !,
  210    random(N) < K.
  211maybe(K, N) :-
  212    must_be(nonneg, K),
  213    must_be(nonneg, N),
  214    domain_error(not_less_than_zero,N-K).
  215
  216
  217                 /*******************************
  218                 *          PERMUTATION         *
  219                 *******************************/
  220
  221%!  random_perm2(?A, ?B, ?X, ?Y) is semidet.
  222%
  223%   Does X=A,Y=B or X=B,Y=A with equal probability.
  224
  225random_perm2(A,B, X,Y) :-
  226    (   maybe
  227    ->  X = A, Y = B
  228    ;   X = B, Y = A
  229    ).
  230
  231
  232                 /*******************************
  233                 *    SET AND LIST OPERATIONS   *
  234                 *******************************/
  235
  236%!  random_member(-X, +List:list) is semidet.
  237%
  238%   X is a random member of   List.  Equivalent to random_between(1,
  239%   |List|), followed by nth1/3. Fails of List is the empty list.
  240%
  241%   @compat Quintus and SICStus libraries.
  242
  243random_member(X, List) :-
  244    must_be(list, List),
  245    length(List, Len),
  246    Len > 0,
  247    N is random(Len),
  248    nth0(N, List, X).
  249
  250%!  random_select(-X, +List, -Rest) is semidet.
  251%!  random_select(+X, -List, +Rest) is det.
  252%
  253%   Randomly select or insert an element.   Either List or Rest must
  254%   be a list.  Fails if List is the empty list.
  255%
  256%   @compat Quintus and SICStus libraries.
  257
  258random_select(X, List, Rest) :-
  259    (   '$skip_list'(Len, List, Tail),
  260        Tail == []
  261    ->  true
  262    ;   '$skip_list'(RLen, Rest, Tail),
  263        Tail == []
  264    ->  Len is RLen+1
  265    ),
  266    !,
  267    Len > 0,
  268    N is random(Len),
  269    nth0(N, List, X, Rest).
  270random_select(_, List, Rest) :-
  271    partial_list(List), partial_list(Rest),
  272    instantiation_error(List+Rest).
  273random_select(_, List, Rest) :-
  274    must_be(list, List),
  275    must_be(list, Rest).
  276
  277%!  randset(+K:int, +N:int, -S:list(int)) is det.
  278%
  279%   S is a sorted list of K unique   random  integers in the range 1..N.
  280%   The implementation uses different techniques  depending on the ratio
  281%   K/N. For small K/N it generates a   set of K random numbers, removes
  282%   the duplicates and adds more numbers until |S| is K. For a large K/N
  283%   it enumerates 1..N and decides  randomly   to  include the number or
  284%   not. For example:
  285%
  286%     ==
  287%     ?- randset(5, 5, S).
  288%     S = [1, 2, 3, 4, 5].          (always)
  289%     ?- randset(5, 20, S).
  290%     S = [2, 7, 10, 19, 20].
  291%     ==
  292%
  293%   @see randseq/3.
  294
  295randset(K, N, S) :-
  296    must_be(nonneg, K),
  297    K =< N,
  298    (   K < N//7
  299    ->  randsetn(K, N, [], S)
  300    ;   randset(K, N, [], S)
  301    ).
  302
  303randset(0, _, S, S) :- !.
  304randset(K, N, Si, So) :-
  305    random(N) < K,
  306    !,
  307    J is K-1,
  308    M is N-1,
  309    randset(J, M, [N|Si], So).
  310randset(K, N, Si, So) :-
  311    M is N-1,
  312    randset(K, M, Si, So).
  313
  314randsetn(K, N, Sofar, S) :-
  315    length(Sofar, Len),
  316    (   Len =:= K
  317    ->  S = Sofar
  318    ;   Needed is K-Len,
  319        length(New, Needed),
  320        maplist(srand(N), New),
  321        (   Sofar == []
  322        ->  sort(New, Sorted)
  323        ;   append(New, Sofar, Sofar2),
  324            sort(Sofar2, Sorted)
  325        ),
  326        randsetn(K, N, Sorted, S)
  327    ).
  328
  329srand(N, E) :-
  330    E is random(N)+1.
  331
  332%!  randseq(+K:int, +N:int, -List:list(int)) is det.
  333%
  334%   S is a list of K unique random   integers in the range 1..N. The
  335%   order is random. Defined as
  336%
  337%     ```
  338%     randseq(K, N, List) :-
  339%           randset(K, N, Set),
  340%           random_permutation(Set, List).
  341%     ```
  342%
  343%   @see randset/3.
  344
  345randseq(K, N, Seq) :-
  346    randset(K, N, Set),
  347    random_permutation_(Set, Seq).
  348
  349%!  random_permutation(+List, -Permutation) is det.
  350%!  random_permutation(-List, +Permutation) is det.
  351%
  352%   Permutation is a random permutation of List. This is intended to
  353%   process the elements of List in   random order. The predicate is
  354%   symmetric.
  355%
  356%   @error instantiation_error, type_error(list, _).
  357
  358random_permutation(List1, List2) :-
  359    is_list(List1),
  360    !,
  361    random_permutation_(List1, List2).
  362random_permutation(List1, List2) :-
  363    is_list(List2),
  364    !,
  365    random_permutation_(List2, List1).
  366random_permutation(List1, List2) :-
  367    partial_list(List1), partial_list(List2),
  368    !,
  369    instantiation_error(List1+List2).
  370random_permutation(List1, List2) :-
  371    must_be(list, List1),
  372    must_be(list, List2).
  373
  374random_permutation_(List, RandomPermutation) :-
  375    key_random(List, Keyed),
  376    keysort(Keyed, Sorted),
  377    pairs_values(Sorted, RandomPermutation).
  378
  379key_random([], []).
  380key_random([H|T0], [K-H|T]) :-
  381    random(K),
  382    key_random(T0, T).
  383
  384%!  partial_list(@Term) is semidet.
  385%
  386%   True if Term is a partial list.
  387
  388partial_list(List) :-
  389    '$skip_list'(_, List, Tail),
  390    var(Tail).
  391
  392:- multifile
  393    prolog:message//1.  394
  395prolog:message(random(no_gmp)) -->
  396    [ 'This version of SWI-Prolog is not compiled with GMP support.'-[], nl,
  397      'Floating point random operations are not supported.'-[]
  398    ]