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            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]).   66
   67
   68/** <module> Random numbers
   69
   70This library is derived from the DEC10   library random. Later, the core
   71random generator was moved to C. The current version uses the SWI-Prolog
   72arithmetic functions to realise this library.  These functions are based
   73on the GMP library.
   74
   75@author         R.A. O'Keefe, V.S. Costa, L. Damas, Jan Wielemaker
   76@see            Built-in function random/1: A is random(10)
   77*/
   78
   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                 *******************************/
   91
   92%!  random(-R:float) is det.
   93%
   94%   Binds R to a new random float in the _open_ interval (0.0,1.0).
   95%
   96%   @see setrand/1, getrand/1 may be used to fetch/set the state.
   97%   @see In SWI-Prolog, random/1 is implemented by the function
   98%        random_float/0.
   99
  100random(R) :-
  101    R is random_float.
  102
  103%!  random_between(+L:int, +U:int, -R:int) is semidet.
  104%
  105%   Binds R to a random integer in [L,U] (i.e., including both L and
  106%   U).  Fails silently if U<L.
  107
  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).
  116
  117
  118%!  random(+L:int, +U:int, -R:int) is det.
  119%!  random(+L:float, +U:float, -R:float) is det.
  120%
  121%   Generate a random integer or float in a   range.  If L and U are
  122%   both integers, R is a random integer   in the half open interval
  123%   [L,U). If L and U are both  floats,   R  is  a float in the open
  124%   interval (L,U).
  125%
  126%   @deprecated Please use random/1 for   generating  a random float
  127%   and random_between/3 for generating a  random integer. Note that
  128%   random_between/3  includes  the  upper  bound,  while  this
  129%   predicate excludes it.
  130
  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                 *******************************/
  147
  148%!  setrand(+State) is det.
  149%!  getrand(-State) is det.
  150%
  151%   Query/set the state of the random   generator.  This is intended
  152%   for  restarting  the  generator  at  a  known  state  only.  The
  153%   predicate  setrand/1  accepts  an  opaque    term   returned  by
  154%   getrand/1. This term may be  asserted,   written  and  read. The
  155%   application may not make other assumptions about this term.
  156%
  157%   For compatibility reasons with older   versions of this library,
  158%   setrand/1 also accepts a term rand(A,B,C), where  A, B and C are
  159%   integers in the range 1..30,000. This   argument is used to seed
  160%   the random generator.  Deprecated.
  161%
  162%   @see    set_random/1 and random_property/1 provide the SWI-Prolog
  163%           native implementation.
  164%   @error  existence_error(random_state, _) is raised if the
  165%           underlying infrastructure cannot fetch the random state.
  166%           This is currently the case if SWI-Prolog is not compiled
  167%           with the GMP library.
  168
  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                 *******************************/
  188
  189%!  maybe is semidet.
  190%
  191%   Succeed/fail with equal probability (variant of maybe/1).
  192
  193maybe :-
  194    random(2) =:= 0.
  195
  196%!  maybe(+P) is semidet.
  197%
  198%   Succeed with probability P, fail with probability 1-P
  199
  200maybe(P) :-
  201    must_be(between(0.0,1.0), P),
  202    random_float < P.
  203
  204%!  maybe(+K, +N) is semidet.
  205%
  206%   Succeed with probability K/N (variant of maybe/1)
  207
  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                 *******************************/
  222
  223%!  random_perm2(?A, ?B, ?X, ?Y) is semidet.
  224%
  225%   Does X=A,Y=B or X=B,Y=A with equal probability.
  226
  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                 *******************************/
  237
  238%!  random_member(-X, +List:list) is semidet.
  239%
  240%   X is a random member of   List.  Equivalent to random_between(1,
  241%   |List|), followed by nth1/3. Fails of List is the empty list.
  242%
  243%   @compat Quintus and SICStus libraries.
  244
  245random_member(_, []) =>
  246    fail.
  247random_member(X, [Single]) =>
  248    X = Single.
  249random_member(X, [First, Second]) =>
  250    (   maybe
  251    ->  X = First
  252    ;   X = Second
  253    ).
  254random_member(X, List) =>
  255    length(List, Len),
  256    N is random(Len),
  257    nth0(N, List, X).
  258
  259%!  random_select(-X, +List, -Rest) is semidet.
  260%!  random_select(+X, -List, +Rest) is det.
  261%
  262%   Randomly select or insert an element.   Either List or Rest must
  263%   be a list.  Fails if List is the empty list.
  264%
  265%   @compat Quintus and SICStus libraries.
  266
  267random_select(X, List, Rest) :-
  268    (   '$skip_list'(Len, List, Tail),
  269        Tail == []
  270    ->  true
  271    ;   '$skip_list'(RLen, Rest, Tail),
  272        Tail == []
  273    ->  Len is RLen+1
  274    ),
  275    !,
  276    Len > 0,
  277    N is random(Len),
  278    nth0(N, List, X, Rest).
  279random_select(_, List, Rest) :-
  280    partial_list(List), partial_list(Rest),
  281    instantiation_error(List+Rest).
  282random_select(_, List, Rest) :-
  283    must_be(list, List),
  284    must_be(list, Rest).
  285
  286%!  random_subseq(+List, -Subseq, -Complement) is det.
  287%!  random_subseq(-List, +Subseq, +Complement) is semidet.
  288%
  289%   Selects  a  random  subsequence  Subseq  of  List,  with  Complement
  290%   containing all elements of List that were not selected. Each element
  291%   of List is included  with  equal   probability  in  either Subseq or
  292%   Complement.
  293%
  294%   random_subseq/3 may also be called with  Subseq and Complement bound
  295%   and List unbound, which will recreate  List by randomly interleaving
  296%   Subseq and Complement. This mode may fail randomly, matching SICStus
  297%   behavior. The failure probability corresponds  to the probability of
  298%   the "forward" mode selecting a   Subseq/Complement  combination with
  299%   different lengths.
  300%
  301%   @compat SICStus 4
  302
  303random_subseq([], [], []).
  304random_subseq([Head|Tail], Subseq, Complement) :-
  305    (   maybe
  306    ->  Subseq = [Head|SubTail],
  307        Complement = CompTail
  308    ;   Subseq = SubTail,
  309        Complement = [Head|CompTail]
  310    ),
  311    random_subseq(Tail, SubTail, CompTail).
  312
  313%!  randset(+K:int, +N:int, -S:list(int)) is det.
  314%
  315%   S is a sorted list of K unique   random  integers in the range 1..N.
  316%   The implementation uses different techniques  depending on the ratio
  317%   K/N. For small K/N it generates a   set of K random numbers, removes
  318%   the duplicates and adds more numbers until |S| is K. For a large K/N
  319%   it enumerates 1..N and decides  randomly   to  include the number or
  320%   not. For example:
  321%
  322%     ==
  323%     ?- randset(5, 5, S).
  324%     S = [1, 2, 3, 4, 5].          (always)
  325%     ?- randset(5, 20, S).
  326%     S = [2, 7, 10, 19, 20].
  327%     ==
  328%
  329%   @see randseq/3.
  330
  331randset(K, N, S) :-
  332    must_be(nonneg, K),
  333    K =< N,
  334    (   K < N//7
  335    ->  randsetn(K, N, [], S)
  336    ;   randset(K, N, [], S)
  337    ).
  338
  339randset(0, _, S, S) :- !.
  340randset(K, N, Si, So) :-
  341    random(N) < K,
  342    !,
  343    J is K-1,
  344    M is N-1,
  345    randset(J, M, [N|Si], So).
  346randset(K, N, Si, So) :-
  347    M is N-1,
  348    randset(K, M, Si, So).
  349
  350randsetn(K, N, Sofar, S) :-
  351    length(Sofar, Len),
  352    (   Len =:= K
  353    ->  S = Sofar
  354    ;   Needed is K-Len,
  355        length(New, Needed),
  356        maplist(srand(N), New),
  357        (   Sofar == []
  358        ->  sort(New, Sorted)
  359        ;   append(New, Sofar, Sofar2),
  360            sort(Sofar2, Sorted)
  361        ),
  362        randsetn(K, N, Sorted, S)
  363    ).
  364
  365srand(N, E) :-
  366    E is random(N)+1.
  367
  368%!  randseq(+K:int, +N:int, -List:list(int)) is det.
  369%
  370%   S is a list of K unique random   integers in the range 1..N. The
  371%   order is random. Defined as
  372%
  373%     ```
  374%     randseq(K, N, List) :-
  375%           randset(K, N, Set),
  376%           random_permutation(Set, List).
  377%     ```
  378%
  379%   @see randset/3.
  380
  381randseq(K, N, Seq) :-
  382    randset(K, N, Set),
  383    random_permutation_(Set, Seq).
  384
  385%!  random_permutation(+List, -Permutation) is det.
  386%!  random_permutation(-List, +Permutation) is det.
  387%
  388%   Permutation is a random permutation of List. This is intended to
  389%   process the elements of List in   random order. The predicate is
  390%   symmetric.
  391%
  392%   @error instantiation_error, type_error(list, _).
  393
  394random_permutation(List1, List2) :-
  395    is_list(List1),
  396    !,
  397    random_permutation_(List1, List2).
  398random_permutation(List1, List2) :-
  399    is_list(List2),
  400    !,
  401    random_permutation_(List2, List1).
  402random_permutation(List1, List2) :-
  403    partial_list(List1), partial_list(List2),
  404    !,
  405    instantiation_error(List1+List2).
  406random_permutation(List1, List2) :-
  407    must_be(list, List1),
  408    must_be(list, List2).
  409
  410random_permutation_(List, RandomPermutation) :-
  411    key_random(List, Keyed),
  412    keysort(Keyed, Sorted),
  413    pairs_values(Sorted, RandomPermutation).
  414
  415key_random([], []).
  416key_random([H|T0], [K-H|T]) :-
  417    random(K),
  418    key_random(T0, T).
  419
  420%!  random_numlist(+P, +L, +U, -List) is det.
  421%
  422%   Unify List with an ascending list of integers between L and U
  423%   (inclusive). Each integer in the range L..U is included with
  424%   probability P.
  425%
  426%   @compat SICStus 4
  427
  428random_numlist(P, L, U, List) :-
  429    must_be(between(0.0, 1.0), P),
  430    must_be(integer, L),
  431    must_be(integer, U),
  432    random_numlist_(P, L, U, List).
  433random_numlist_(_P, L, U, List) :-
  434    L > U,
  435    !,
  436    List = [].
  437random_numlist_(P, L, U, List) :-
  438    (   maybe(P)
  439    ->  List = [L|Tail]
  440    ;   List = Tail
  441    ),
  442    L1 is L + 1,
  443    random_numlist_(P, L1, U, Tail).
  444
  445%!  partial_list(@Term) is semidet.
  446%
  447%   True if Term is a partial list.
  448
  449partial_list(List) :-
  450    '$skip_list'(_, List, Tail),
  451    var(Tail).
  452
  453:- multifile
  454    prolog:message//1.  455
  456prolog:message(random(no_gmp)) -->
  457    [ 'This version of SWI-Prolog is not compiled with GMP support.'-[], nl,
  458      'Floating point random operations are not supported.'-[]
  459    ]