File: sltimer.f

package info (click to toggle)
scalapack 2.2.2-1
  • links: PTS, VCS
  • area: main
  • in suites: sid, trixie
  • size: 37,012 kB
  • sloc: fortran: 339,113; ansic: 74,517; makefile: 1,494; sh: 34
file content (401 lines) | stat: -rw-r--r-- 11,067 bytes parent folder | download | duplicates (12)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
      SUBROUTINE SLBOOT()
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*  Purpose
*  =======
*
*  SLBOOT (re)sets all timers to 0, and enables SLtimer.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
      DOUBLE PRECISION   STARTFLAG, ZERO
      PARAMETER          ( STARTFLAG = -5.0D+0, ZERO = 0.0D+0 )
*     ..
*     .. Local Scalars ..
      INTEGER            I
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
      DISABLED = .FALSE.
      DO 10 I = 1, NTIMER
         CPUSEC( I )  = ZERO
         WALLSEC( I ) = ZERO
         CPUSTART( I )  = STARTFLAG
         WALLSTART( I ) = STARTFLAG
   10 CONTINUE
*
      RETURN
*
*     End of SLBOOT
*
      END
*
      SUBROUTINE SLTIMER( I )
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*     .. Scalar Arguments ..
      INTEGER            I
*     ..
*
*  Purpose
*  =======
*
*  SLtimer provides a "stopwatch" functionality cpu/wall timer
*  (in seconds).  Up to 64 separate timers can be functioning at once.
*  The first call starts the timer, and the second stops it.  This
*  routine can be disenabled, so that calls to the timer are ignored.
*  This feature can be used to make sure certain sections of code do
*  not affect timings, even if they call routines which have SLtimer
*  calls in them.
*
*  Arguments
*  =========
*
*  I       (global input) INTEGER
*          The timer to stop/start.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
      DOUBLE PRECISION   STARTFLAG
      PARAMETER          ( STARTFLAG = -5.0D+0 )
*     ..
*     .. External Functions ..
      DOUBLE PRECISION   DCPUTIME00, DWALLTIME00
      EXTERNAL           DCPUTIME00, DWALLTIME00
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
*     If timing disabled, return
*
      IF( DISABLED )
     $   RETURN
*
      IF( WALLSTART( I ).EQ.STARTFLAG ) THEN
*
*        If timer has not been started, start it
*
         WALLSTART( I ) = DWALLTIME00()
         CPUSTART( I )  = DCPUTIME00()
*
      ELSE
*
*        Stop timer and add interval to count
*
         CPUSEC( I ) = CPUSEC( I ) + DCPUTIME00() - CPUSTART( I )
         WALLSEC( I ) = WALLSEC( I ) + DWALLTIME00() - WALLSTART( I )
         WALLSTART( I ) = STARTFLAG
*
      END IF
*
      RETURN
*
*     End of SLTIMER
*
      END
*
      SUBROUTINE SLENABLE()
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*  Purpose
*  =======
*
*  SLENABLE sets it so calls to SLtimer are not ignored.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
      DISABLED = .FALSE.
*
      RETURN
*
      END
*
      SUBROUTINE SLDISABLE()
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*  Purpose
*  =======
*
*  SLDISABLE sets it so calls to SLTIMER are ignored.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
      DISABLED = .TRUE.
*
      RETURN
*
*     End of SLDISABLE
*
      END
*
      DOUBLE PRECISION FUNCTION SLINQUIRE( TIMETYPE, I )
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*     .. Scalar Arguments ..
      CHARACTER*1        TIMETYPE
      INTEGER            I
*     ..
*
*  Purpose
*  =======
*
*  SLINQUIRE returns wall or cpu time that has accumulated in timer I.
*
*  Arguments
*  =========
*
*  TIMETYPE (global input) CHARACTER
*           Controls what time will be returned:
*           = 'W': wall clock time is returned,
*           = 'C': CPU time is returned (default).
*
*  I        (global input) INTEGER
*           The timer to return.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
      DOUBLE PRECISION   ERRFLAG
      PARAMETER          ( ERRFLAG = -1.0D+0 )
*     ..
*     .. Local Scalars ..
      DOUBLE PRECISION   TIME
*     ..
*     .. External Functions ..
      LOGICAL            LSAME
      DOUBLE PRECISION   DCPUTIME00, DWALLTIME00
      EXTERNAL           DCPUTIME00, DWALLTIME00, LSAME
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
      IF( LSAME( TIMETYPE, 'W' ) ) THEN
*
*        If walltime not available on this machine, return -1 flag
*
         IF( DWALLTIME00().EQ.ERRFLAG ) THEN
            TIME = ERRFLAG
         ELSE
            TIME = WALLSEC( I )
         END IF
      ELSE
         IF( DCPUTIME00().EQ.ERRFLAG ) THEN
            TIME = ERRFLAG
         ELSE
            TIME = CPUSEC( I )
         END IF
      END IF
*
      SLINQUIRE = TIME
*
      RETURN
*
*     End of SLINQUIRE
*
      END
*
      SUBROUTINE SLCOMBINE( ICTXT, SCOPE, OP, TIMETYPE, N, IBEG,
     $                      TIMES )
*
*  -- ScaLAPACK tools routine (version 1.7) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     May 1, 1997
*
*     .. Scalar Arguments ..
      CHARACTER          OP, SCOPE, TIMETYPE
      INTEGER            IBEG, ICTXT, N
*     ..
*     .. Array Arguments ..
      DOUBLE PRECISION   TIMES( N )
*     ..
*
*  Purpose
*  =======
*
*  SLCOMBINE takes the timing information stored on a scope of processes
*  and combines them into the user's TIMES array.
*
*  Arguments
*  =========
*
*  ICTXT    (local input) INTEGER
*           The BLACS context handle.
*
*  SCOPE    (global input) CHARACTER
*           Controls what processes in grid participate in combine.
*           Options are 'Rowwise', 'Columnwise', or 'All'.
*
*  OP       (global input) CHARACTER
*           Controls what combine should be done:
*           = '>': get maximal time on any process (default),
*           = '<': get minimal time on any process,
*           = '+': get sum of times across processes.
*
*  TIMETYPE (global input) CHARACTER
*           Controls what time will be returned in TIMES:
*           = 'W': wall clock time,
*           = 'C': CPU time (default).
*
*  N        (global input) INTEGER
*           The number of timers to combine.
*
*  IBEG     (global input) INTEGER
*           The first timer to be combined.
*
*  TIMES    (global output) DOUBLE PRECISION array, dimension (N)
*           The requested timing information is returned in this array.
*
*  =====================================================================
*
*     .. Parameters ..
      INTEGER            NTIMER
      PARAMETER          ( NTIMER = 64 )
      DOUBLE PRECISION   ERRFLAG
      PARAMETER          ( ERRFLAG = -1.0D+0 )
*     ..
*     .. Local Scalars ..
      LOGICAL            TMPDIS
      INTEGER            I
*     ..
*     .. External Subroutines ..
      EXTERNAL           DGAMX2D, DGAMN2D, DGSUM2D
*     ..
*     .. External Functions ..
      LOGICAL            LSAME
      DOUBLE PRECISION   DCPUTIME00, DWALLTIME00
      EXTERNAL           DCPUTIME00, DWALLTIME00, LSAME
*     ..
*     .. Common Blocks ..
      LOGICAL            DISABLED
      DOUBLE PRECISION   CPUSEC( NTIMER ), CPUSTART( NTIMER ),
     $                   WALLSEC( NTIMER ), WALLSTART( NTIMER )
      COMMON /SLTIMER00/ CPUSEC, WALLSEC, CPUSTART, WALLSTART, DISABLED
*     ..
*     .. Executable Statements ..
*
*     Disable timer for combine operation
*
      TMPDIS = DISABLED
      DISABLED = .TRUE.
*
*     Copy timer information into user's times array
*
      IF( LSAME( TIMETYPE, 'W' ) ) THEN
*
*        If walltime not available on this machine, fill in times
*        with -1 flag, and return
*
         IF( DWALLTIME00().EQ.ERRFLAG ) THEN
            DO 10 I = 1, N
               TIMES( I ) = ERRFLAG
   10       CONTINUE
            RETURN
         ELSE
            DO 20 I = 1, N
               TIMES( I ) = WALLSEC( IBEG + I - 1 )
   20       CONTINUE
         END IF
      ELSE
         IF( DCPUTIME00().EQ.ERRFLAG ) THEN
            DO 30 I = 1, N
               TIMES( I ) = ERRFLAG
   30       CONTINUE
            RETURN
         ELSE
            DO 40 I = 1, N
               TIMES( I ) = CPUSEC( IBEG + I - 1 )
   40       CONTINUE
         END IF
      ENDIF
*
*     Combine all nodes' information, restore disabled, and return
*
      IF( OP.EQ.'>' ) THEN
         CALL DGAMX2D( ICTXT, SCOPE, ' ', N, 1, TIMES, N, -1, -1,
     $                 -1, -1, 0 )
      ELSE IF( OP.EQ.'<' ) THEN
         CALL DGAMN2D( ICTXT, SCOPE, ' ', N, 1, TIMES, N, -1, -1,
     $                 -1, -1, 0 )
      ELSE IF( OP.EQ.'+' ) THEN
         CALL DGSUM2D( ICTXT, SCOPE, ' ', N, 1, TIMES, N, -1, 0 )
      ELSE
         CALL DGAMX2D( ICTXT, SCOPE, ' ', N, 1, TIMES, N, -1, -1,
     $                 -1, -1, 0 )
      END IF
*
      DISABLED = TMPDIS
*
      RETURN
*
*     End of SLCOMBINE
*
      END