1% ----------------------------------------------------------------------
2% BEGIN LICENSE BLOCK
3% Version: CMPL 1.1
4%
5% The contents of this file are subject to the Cisco-style Mozilla Public
6% License Version 1.1 (the "License"); you may not use this file except
7% in compliance with the License.  You may obtain a copy of the License
8% at www.eclipse-clp.org/license.
9%
10% Software distributed under the License is distributed on an "AS IS"
11% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
12% the License for the specific language governing rights and limitations
13% under the License.
14%
15% The Original Code is  The ECLiPSe Constraint Logic Programming System.
16% The Initial Developer of the Original Code is  Cisco Systems, Inc.
17% Portions created by the Initial Developer are
18% Copyright (C) 1994-2006 Cisco Systems, Inc.  All Rights Reserved.
19%
20% Contributor(s): ECRC GmbH
21% Contributor(s): IC-Parc, Imperal College London
22%
23% END LICENSE BLOCK
24%
25% System:	ECLiPSe Constraint Logic Programming System
26% Version:	$Id: par_util.pl,v 1.2 2009/07/16 09:11:24 jschimpf Exp $
27% ----------------------------------------------------------------------
28
29%
30% ECLiPSe PROLOG LIBRARY MODULE
31%
32% IDENTIFICATION:	par_util.pl
33%
34% AUTHOR:		Joachim Schimpf
35%
36% CONTENTS:
37%			par_member(?Element, +List)
38%			par_delete(?Element, +List, ?Rest)
39%			par_between(+From, +To, ?I)
40%			par_maplist(+Pred, +ListIn, ?ListOut)
41%
42%			statistics_par
43%			statistics_par_reset
44%
45%			Goal1 & Goal2
46%
47% DESCRIPTION:		Parallel versions of various predicates.
48%			The semantics of par_member/2, par_maplist/3
49%			and &/2 is not exactly the same as the
50%			corresponding sequential version.
51%
52
53:- module(par_util).
54:- pragma(nodebug).
55
56:- comment(categories, ["Algorithms"]).
57:- comment(summary, "Parallel versions of various predicates").
58:- comment(author, "Joachim Schimpf, ECRC Munich").
59:- comment(copyright, "Cisco Systems, Inc").
60:- comment(date, "$Date: 2009/07/16 09:11:24 $").
61:- comment(par_member/2, [template:"par_member(?Element, +List)",
62    summary:"Parallel version of member/2",
63    desc:html("Parallel version of member/2, i.e.  selects elements from
64    the given list in parallel.  Note that it cannot work backwards
65    and generate lists like member/2 can, the list must be a proper list.")]).
66:- comment(par_delete/3, [template:"par_delete(?Element, ?List, ?Rest)",
67    summary:"Parallel version of delete/3"]).
68:- comment(par_between/3, [template:"par_between(+From, +To, ?I)",
69    summary:"Generates integers between From and To in parallel",
70    see_also:[fork/2, between/3, between/4]]).
71:- comment(par_maplist/3, [template:"par_maplist(+Pred, +In, ?Out)",
72    summary:"Parallel version of maplist/3",
73    desc:html("Parallel version of maplist/3.  The semantics is not
74    exactly the same as maplist/3:  It does not work backwards and it
75    does not cope with aliasing between the In and the Out list, since
76    it is implemented on top of findall/3.  There will only be a
77    performance gain if the mapping predicate does enough computation
78    to make the overhead pay off."),
79    see_also:[maplist/3]]).
80:- comment((&)/2, [template:"Goal1 & Goal2",
81    summary:"Parallel AND operator implemented on top of OR-parallelism",
82    desc:html("Parallel AND operator implemented on top of
83    OR-parallelism.  This will only pay off for sufficiently
84    coarse-grained computations in Goal1 and Goal2.")]).
85
86:- export
87	(&)/2,
88	par_between/3,
89	par_delete/3,
90	par_maplist/3,
91	par_member/2,
92	statistics_par/0,
93	statistics_par_reset/0.
94
95:- export op(950, xfy, (&)).
96
97
98:- import worker_statistics/2, worker_statistics_reset/1 from sepia_kernel.
99
100% Parallel member(?, +List), it can't generate lists!
101
102par_member(X, List) :-
103	List = [_|_],
104	Arr =.. [arr|List],
105	functor(Arr, arr, N),
106	N1 is N+1,
107	fork(N, I),
108	I1 is N1-I,
109	arg(I1, Arr, X).
110
111
112:- parallel par_delete/3.
113par_delete(A, [A|C], C).
114par_delete(A, [B|C], [B|D]) :-
115	par_delete(A, C, D).
116
117
118par_between(From, To, X) :-
119	To1 is To+1,
120	N is To1-From,
121	N > 0,
122	fork(N, I),
123	X is To1-I.
124
125
126:- tool((&)/2, '&_body'/3).
127
128'&_body'(Goal1, Goal2, Module) :-
129	findall(Sol, parand(Sol, Goal1, Goal2, Module), Bag),
130	member(a-Goal1, Bag),
131	member(b-Goal2, Bag).
132
133:- parallel parand/4.
134:- mode parand(-,+,+,+).
135parand(a-Goal1, Goal1, _, Module) :- call(Goal1)@Module.
136parand(b-Goal2, _, Goal2, Module) :- call(Goal2)@Module.
137
138
139:- tool(par_maplist/3, par_maplist_body/4).
140
141par_maplist_body(Pred, In, Out, Module) :-
142	findall(Sol, map_elements(Pred, In, Sol, Module), Out0),
143	sort(1, >=, Out0, Out1),
144	strip_key(Out1, Out).
145
146map_elements(Pred, In, I-Xout, Module) :-
147	Pred =.. PL,
148	append(PL, [Xin, Xout], NewPred),
149	Call =.. NewPred,
150	InArr =.. [in|In],
151	functor(InArr, in, N),
152	N1 is N+1,
153	fork(N, I),
154	I1 is N1-I,
155	arg(I1, InArr, Xin),
156	( call(Call)@Module, true -> true ).
157
158strip_key([], []).
159strip_key([_-X|Xs], [X|Ys]) :- strip_key(Xs, Ys).
160
161
162% Parallel statistics
163
164statistics_par :-
165	writeln(" Wrkr Jobs Prun Published Copy      Copied  Idling Working Copying Scheduling"),
166	writeln("   ID    #    # cpts alts    #       bytes      ms      ms      ms      ms\n"),
167	get_flag(workerids, _Host:AliveIds+SleepIds),
168	(member(Wid, AliveIds) ; member(Wid, SleepIds)),
169	worker_statistics(Wid, Data),
170	arg(1, Data, Jobs),
171	arg(2, Data, Prunes),
172	arg(4, Data, CopyFromCnt),
173	arg(5, Data, CopyFromBytes),
174	arg(8, Data, _Publish),
175	arg(9, Data, PubChpts),
176	arg(10, Data, PubAlts),
177	IdleMs is arg(14, Data) + arg(23, Data),
178	WorkMs is arg(15, Data),
179	CopyMs is arg(17, Data) + arg(18, Data) + arg(22, Data),
180	SchedMs is arg(16, Data) + arg(19, Data) + arg(20, Data) + arg(21, Data),
181	printf("%5d%5d%5d%5d%5d%5d%12d%8.0f%8.0f%8.0f%8.0f\n",
182		[Wid, Jobs, Prunes, PubChpts, PubAlts, CopyFromCnt,
183		 CopyFromBytes, IdleMs, WorkMs, CopyMs, SchedMs]),
184	fail.
185statistics_par.
186
187statistics_par_reset :-
188	get_flag(workerids, _Host:AliveIds+SleepIds),
189	(member(Wid, AliveIds) ; member(Wid, SleepIds)),
190	worker_statistics_reset(Wid),
191	fail.
192statistics_par_reset.
193
194