1 % (c) 2009-2021 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(random_permutations, [get_num_bits/3,
6 get_masks/3,
7 random_permutation_element/10,
8 init_random_permutations/0,
9
10 enum_fd_random/3 % high-level predicate
11 ]).
12
13 :- use_module(probsrc(module_information),[module_info/2]).
14 :- module_info(group,cbc).
15 :- module_info(description,'This module provides on-the-fly construction of random permutations of intervals.').
16
17 foreign_resource(random_permutations,[get_num_bits,draw_index]).
18 foreign(get_num_bits, c, get_num_bits(+integer,-integer,-integer)).
19 foreign(draw_index, c, draw_index(+integer,+integer,+integer,+integer,+integer,+integer,+integer,+integer,-integer,-integer)).
20
21 :- dynamic is_initialised/0.
22
23 :- use_module(probsrc(pathes_lib),[safe_load_foreign_resource/2]).
24
25 init_random_permutations :- is_initialised,!.
26 init_random_permutations :-
27 safe_load_foreign_resource(random_permutations,random_permutations),
28 assertz(is_initialised).
29
30
31 get_masks(HalfNumBits,LeftMask,RightMask) :-
32 RightMask is (1 << HalfNumBits) - 1,
33 LeftMask is RightMask << HalfNumBits.
34
35 random_permutation_element(Index,MaxIndex,From,To,Seed,NumBits,LeftMask,RightMask,RandomElement,NextIndex) :-
36 draw_index(Index,MaxIndex,Seed,NumBits,LeftMask,RightMask,From,To,DrawnElement,NextIndex),
37 % working on a 4^x long interval. thus, we might pick a number that is too large
38 % if this happens, we just pick a new one
39 % to avoid context switching overhead, this is now done inside the C code
40 RandomElement is DrawnElement + From.
41
42
43 :- use_module(library(random),[random/1]).
44 % enumerate Prolog/FD variable between low and up in random order
45 enum_fd_random(Var,Low,Up) :-
46 init_random_permutations,
47 IntervalLength is Up - Low + 1,
48 get_num_bits(IntervalLength,MaxIdx,NumBits),
49 get_masks(NumBits,LeftMask,RightMask),
50 % the seed relies on the random predicate, not on now/1, thus prob can be made deterministic by setting a central random seed
51 random(TempSeed),
52 Seed is floor(TempSeed * 10000),
53 ? enum_fd_random_aux(Var,0,MaxIdx,Low,Up,Seed,NumBits,LeftMask,RightMask).
54
55 enum_fd_random_aux(Var,CurIdx,MaxIdx,From,To,Seed,NumBits,LeftMask,RightMask) :-
56 random_permutation_element(CurIdx,MaxIdx,From,To,Seed,NumBits,LeftMask,RightMask,Drawn,NextIdx),
57 ? (Var=Drawn ; enum_fd_random_aux(Var,NextIdx,MaxIdx,From,To,Seed,NumBits,LeftMask,RightMask)).
58
59
60 % -------------------
61 % Testing predicates
62 % -------------------
63 % unused at the moment:
64 %:- public shuffle/2.
65 %:- use_module(library(system)).
66 %shuffle(From,To) :-
67 % init_random_permutations,
68 % IntervalLength is To - From + 1,
69 % get_num_bits(IntervalLength,MaxIndex,NumBits),
70 % get_masks(NumBits,LeftMask,RightMask),
71 % now(Seed),
72 % shuffle(From,0,To,MaxIndex,Seed,NumBits,LeftMask,RightMask).
73 %shuffle(From,CurIdx,To,MaxIndex,Seed,NumBits,LeftMask,RightMask) :-
74 % random_permutation_element(CurIdx,MaxIndex,From,To,Seed,NumBits,LeftMask,RightMask,Drawn,NextIdx),
75 % format('Drawing index ~w resulted in ~w~n',[CurIdx,Drawn]),
76 % shuffle(From,NextIdx,To,MaxIndex,Seed,NumBits,LeftMask,RightMask).
77 %shuffle(_,_,_,_,_,_,_,_).