/[MITgcm]/MITgcm/tools/OAD_support/revolve.F90
ViewVC logotype

Contents of /MITgcm/tools/OAD_support/revolve.F90

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (show annotations) (download)
Sat Mar 9 17:17:39 2013 UTC (11 years, 1 month ago) by utke
Branch: MAIN
CVS Tags: checkpoint64g, checkpoint64f
Changes since 1.1: +337 -102 lines
resync

1 !> \mainpage
2 !! This is a Fortran9X adaptation of the functionality of Revolve; see Alg. 799 published as \cite Griewank2000ARA .
3 !! The interface of the routines differs from the cited revolve implementation
4 !! found in Adol-C and has been designed to be more in line with the
5 !! Fortran 9X language features. A minor extension is the optional `bundle` parameter that allows to treat as many loop
6 !! iterations in one tape/adjoint sweep. If `bundle` is 1, the default, then the behavior is that of Alg. 799.
7 !!
8 !! The implementation (written by J. Utke) is contained in revolve.f90, the use is illustrated in the `Examples` directory.
9 !!
10 !! The mercurial repository with the latest version can be found at:
11 !! <a href="http://mercurial.mcs.anl.gov/ad/RevolveF9X">http://mercurial.mcs.anl.gov/ad/RevolveF9X</a>
12 !!
13
14
15 !> the module containing the revolve implementation
16 !!
17 MODULE revolve
18 IMPLICIT NONE
19
20 PUBLIC :: rvInit, rvVerbose, rvNextAction, rvGuess, rvFactor, &
21 rvStore, rvRestore, rvForward, rvFirstUTurn, rvUTurn, rvDone, rvError
22
23 PRIVATE :: &
24 ourSteps, ourACP, ourCStart, ourCEnd, ourVerbosity, &
25 ourNumFwd , ourNumInv, ourNumStore, ourRWCP, ourPrevCEnd, ourFirstUTurned, &
26 chkRange, forwdCount
27
28 !> store a checkpoint now
29 !! equivalent to TAKESHOT in Alg. 799
30 INTEGER, PARAMETER :: rvStore =1
31
32 !> restore a checkpoint now
33 !! equivalent to RESTORE in Alg. 799
34 INTEGER, PARAMETER :: rvRestore =2
35
36 !> execute iteration(s) forward
37 !! equivalent to ADVANCE in Alg. 799
38 INTEGER, PARAMETER :: rvForward =3
39
40 !> tape iteration(s); optionally leave to return later; and (upon return) do the adjoint(s)
41 !! equivalent to FIRSTTURN in Alg. 799
42 INTEGER, PARAMETER :: rvFirstUTurn =4
43
44 !> tape iteration(s) and do the adjoint(s)
45 !! equivalent to YOUTURN in Alg. 799
46 INTEGER, PARAMETER :: rvUTurn =5
47
48 !> we are done with adjoining the loop
49 !! equivalent to the `terminate` enum value in Alg. 799
50 INTEGER, PARAMETER :: rvDone =6
51
52 !> an error has occurred
53 !! equivalent to the `error` enum value in Alg. 799;
54 !! see also `errorMsg` in \ref rvAction
55 INTEGER, PARAMETER :: rvError =7
56
57 !> this encapsulates all the information needed to perfrom the correct action
58 !! an instance is returned from \ref rvNextAction
59 TYPE rvAction
60 !> the action that is to be implemented, termination, or error;
61 !! the value must be one of:
62 !! `rvStore`, `rvRestore`, `rvForward`,
63 !! `rvFirstUTurn`, `rvUTurn`, `rvDone`, `rvError`
64 INTEGER :: actionFlag = 0
65
66 !> assumptions:
67 !! - the loop iterations are numbered in range [0,`ourSteps`-1]
68 !! - the model state is the input to the iteration numbered `startIteration`
69 !!
70 !! the interpretation is as follows based on the value of `actionFlag`:
71 !! - `rvForward`: execute iterations as the loop: `do currentIteration=startIteration, iteration-1`
72 !! - `rvRestore`: restores model state at `iteration` (here it has the same value as `startIteration`)
73 !! - `rvFirstUTurn`/`rvUTurn`: tape iterations in loop: do currentIteration=startIteration, iteration-1`
74 !! followed by adjoint sweep over iterations in loop: do currentIteration=iteration-1,startIteration,-1
75 !!
76 !! for all other values of `actionFlag` the value of `iteration` is meaningless
77 INTEGER :: iteration = 0
78
79 !> assuming the loop iterations are in [0,ourSteps-1] and `currentIteration` variable is maintained,
80 !! the interpretation is as follows based on the value of `actionFlag`:
81 !! - `rvForward`: execute iterations as the loop: `do currentIteration, iteration-1`
82 !! - `rvRestore`: set `currentIteration=iteration`
83 !!
84 !! for all other values of `actionFlag` the value of `iteration` is meaningless
85 INTEGER :: startIteration = 0
86
87 !> the checkpoint number to be stored to restored
88 !! the value is meaninfull only if `actionFlag` is set to `rvStore` or `rvRestore`;
89 !!
90 !! This is approximately equivalent to `checks` in Alg. 799.
91 INTEGER :: cpNum = 0
92
93 !> if an error has occurred `actionFlag` will be set to `rvError` and this will contain an error message
94 CHARACTER(80) :: errorMsg
95 END TYPE rvAction
96
97 !> the number of iteration steps; set by calling \ref rvInit; not supposed to be set/used directly by the user;
98 !! note that the iterations are expected to range in [0, ourSteps-1];
99 !!
100 !! equivalent to `steps` in Alg. 799
101 INTEGER :: ourSteps = 0 ! number of steps
102
103 !> the number of iterations that may be bundled for a taping/adjoining sweep;
104 !! set by calling \ref rvInit; not supposed to be set/used directly by the user;
105 !!
106 !! the default is 1 loop iteration which makes it equivalent to Alg. 799
107 INTEGER :: ourBundle = 1
108
109 !> the number of iterations in the last bundle
110 !! set by calling \ref rvInit; not supposed to be set/used directly by the user;
111 !!
112 !! the default is 1 (for `ourBundle` = 1) which makes it equivalent to Alg. 799
113 INTEGER :: ourTail = 1
114
115 !> the number of checkpoints (ACP=AllowedCheckPoints) that can be stored at any time during the loop execution
116 !! set by calling \ref rvInit; not supposed to be set/used directly by the user
117 !!
118 !! equivalent to `snaps` in Alg. 799
119 INTEGER :: ourACP = 0
120
121 !> current subrange start;
122 !! not to be set/referemced directly by the user
123 !!
124 !! approximately equivalent to `capo` in Alg. 799
125 INTEGER :: ourCStart = 0
126
127 !> current subrange end;
128 !! not to be set/referemced directly by the user
129 !!
130 !! approximately equivalent to `fine` in Alg. 799
131 INTEGER :: ourCEnd = 0
132
133 !> count of the forward steps; diagnostic only
134 INTEGER :: ourNumFwd = 0
135
136 !> count of invocations to \ref rvNextAction ; diagnostic only
137 INTEGER :: ourNumInv = 0
138
139 !> count of checkpoint stores; diagnostic only
140 INTEGER :: ourNumStore = 0
141
142 !> checkpoint currently (re)stored - the first checkpoint is numbered 0;
143 !! not to be set/referemced directly by the user
144 INTEGER :: ourRWCP = -1
145
146 !> previous subrange end;
147 !! not to be set/referemced directly by the user
148 INTEGER :: ourPrevCEnd = 0
149
150 !> have we first uturned already?;
151 !! not to be set/referemced directly by the user
152 LOGICAL :: ourFirstUturned = .FALSE.
153
154 !> vector of step numbers indexed by checkpoint;
155 !! not to be set/referemced directly by the user
156 INTEGER, DIMENSION(:), ALLOCATABLE :: ourStepOf
157
158 !> for debugging purposes; values imply:
159 !! - 0 includes errors
160 !! - 1 includes summary info
161 !! - 2 includes iterations with checkpoints stored
162 !! - 3 includes all action results
163 !!
164 !! set via \ref rvVerbose
165 INTEGER :: ourVerbosity = 0
166
167 CONTAINS
168
169 !--------------------------------------------------------------------*
170
171 !> method to initialize the internal state; must be called before any call to \ref rvNextAction
172 !! @param steps the total number of steps in the iteration; equivalent to `steps` in Alg. 799
173 !! @param checkpoints the total number of checkpoints allowed to be stored at any time; equivalent to `snaps` in Alg. 799
174 !! @param errorMsg set when an error condition occurs; else set to `"none"`
175 !! @param anActionInstance if supplied initializes its contents
176 !! @param bundle if supplied initializes `ourBundle`
177 !! @return `.true.` if successfull, else `.false.` ansd `errorMsg` will be set
178 FUNCTION rvInit(steps,checkpoints,errorMsg,anActionInstance,bundle)
179 IMPLICIT NONE
180 LOGICAL :: rvInit
181 INTEGER, INTENT(IN) :: steps
182 INTEGER, INTENT(IN) :: checkpoints
183 CHARACTER(*), INTENT(OUT) :: errorMsg
184 type(rvAction), optional :: anActionInstance
185 INTEGER, INTENT(IN), optional :: bundle
186 INTEGER :: predFwdCnt ! predicted forward count
187 rvInit = .TRUE.
188 errorMsg ='none'
189 IF (present(anActionInstance)) THEN
190 ! same as default init above
191 anActionInstance%actionFlag = 0
192 anActionInstance%iteration = 0
193 anActionInstance%cpNum = 0
194 END IF
195 IF (present(bundle)) THEN
196 ourBundle = bundle
197 END IF
198 IF (ourBundle<1 .OR. ourBundle>steps) THEN
199 rvInit=.FALSE.
200 errorMsg = "revolve::rvInit: bundle parameter out of range [1,steps]"
201 ELSEIF (steps<0) THEN
202 rvInit=.FALSE.
203 errorMsg = 'revolve::rvInit: negative steps'
204 ELSEIF (checkpoints<0) THEN
205 rvInit=.FALSE.
206 errorMsg = 'revolve::rvInit: negative checkpoints'
207 ELSE
208 ourCStart = 0
209 ourSteps = steps
210 IF (ourBundle .gt. 1) THEN
211 ourTail=modulo(ourSteps,ourBundle)
212 ourSteps=ourSteps/ourBundle
213 IF (ourTail>0) THEN
214 ourSteps=ourSteps+1
215 ELSE
216 ourTail=ourBundle
217 END IF
218 END IF
219 ourCEnd = ourSteps
220 ourACP = checkpoints
221 ourNumFwd = 0
222 ourNumInv = 0
223 ourNumStore = 0
224 ourRWCP = -1
225 ourPrevCEnd = 0
226 ourFirstUTurned = .FALSE.
227
228 IF (ALLOCATED(ourStepOf)) THEN
229 DEALLOCATE(ourStepOf)
230 END IF
231 IF(.NOT.ALLOCATED(ourStepOf)) THEN
232 ALLOCATE(ourStepOf(0:ourACP))
233 END IF
234
235 IF (ourVerbosity>0) THEN
236 predFwdCnt = forwdCount(steps,ourACP,ourBundle)
237 IF (predFwdCnt==-1) THEN
238 errorMsg='revolve::rvInit: error returned by revolve::forwdCount'
239 rvInit=.FALSE.
240 RETURN
241 ELSE
242 WRITE (*,'(A)') 'prediction:'
243 WRITE (*,'(A,I7)') ' overhead forward steps : ', predFwdCnt
244 WRITE (*,'(A,F8.4)') ' overhead factor : ', dble(predFwdCnt)/(steps)
245 END IF
246 END IF
247 END IF
248 END FUNCTION rvInit
249
250 !--------------------------------------------------------------------*
251
252 !> method to set the verbosity to a level in [0-3] as described for `ourVerbosity`
253 SUBROUTINE rvVerbose(level)
254 IMPLICIT NONE
255 INTEGER, INTENT(IN) :: level
256 ourVerbosity=level
257 END SUBROUTINE rvVerbose
258
259 !--------------------------------------------------------------------*
260 !> the method to determine the next action; to be called in an unbound loop after \ref rvInit
261 !! @return an instance of `rvAction` set to describe the next action (see the member documentation);
262 !!
263 !! this method modifies the internal state; it is approximately equivalent to the method `revolve` in Alg. 799
264 FUNCTION rvNextAction()
265 IMPLICIT NONE
266 REAL :: bino1, bino2, bino3, bino4, bino5
267
268 !> available checkpoint slots
269 INTEGER :: availCP
270
271 !> local copy of previous subrange start
272 INTEGER :: prevCStart
273
274 INTEGER :: range
275 INTEGER :: reps
276 INTEGER :: i
277 type(rvAction) :: rvNextAction
278 IF (ourNumInv==0) THEN
279 ! first invocation
280 DO i = 0, ourACP
281 ourStepOf(i) = 0
282 END DO
283 ourStepOf(0) = ourCStart - 1
284 END IF
285 prevCStart = ourCStart
286 ourNumInv = ourNumInv + 1
287 IF ((ourCEnd-ourCStart)==0) THEN
288 ! nothing in current subrange
289 IF ((ourRWCP==(-1)) .OR. (ourCStart==ourStepOf(0))) THEN
290 ! we are done
291 ourRWCP = ourRWCP - 1
292 IF (ourVerbosity>2) THEN
293 WRITE (*,FMT='(A)') ' done'
294 END IF
295 IF (ourVerbosity>0) THEN
296 WRITE (*,'(A)') 'summary:'
297 WRITE (*,'(A,I8)') ' overhead forward steps:', ourNumFwd
298 WRITE (*,'(A,I8)') ' CP stores :', ourNumStore
299 WRITE (*,'(A,I8)') ' rvNextAction calls :', ourNumInv
300 END IF
301 rvNextAction%actionFlag = rvDone
302 ELSE
303 ourCStart = ourStepOf(ourRWCP)
304 ourPrevCEnd = ourCEnd
305 rvNextAction%actionFlag = rvRestore
306 END IF
307 ELSE IF ((ourCEnd-ourCStart)==1) THEN
308 ourCEnd = ourCEnd - 1
309 ourPrevCEnd = ourCEnd
310 IF ((ourRWCP>=0) .AND. (ourStepOf(ourRWCP)==ourCStart)) ourRWCP = ourRWCP - 1
311 IF (.NOT.ourFirstUTurned) THEN
312 rvNextAction%actionFlag = rvFirstUTurn
313 ourFirstUTurned = .TRUE.
314 ELSE
315 rvNextAction%actionFlag = rvUTurn
316 END IF
317 ELSE IF ((ourRWCP==(-1)) .OR. (ourStepOf(ourRWCP)/=ourCStart)) THEN
318 ourRWCP = ourRWCP + 1
319 IF (ourRWCP+1>ourACP) THEN
320 rvNextAction%actionFlag = rvError
321 rvNextAction%errorMsg='revolve::rvNextAction: insufficient allowed checkpoints'
322 RETURN
323 ELSE
324 ourStepOf(ourRWCP) = ourCStart
325 ourNumStore = ourNumStore + 1
326 ourPrevCEnd = ourCEnd
327 rvNextAction%actionFlag = rvStore
328 END IF
329 ELSE IF ((ourPrevCEnd<ourCEnd) .AND. (ourACP==ourRWCP+1)) THEN
330 rvNextAction%actionFlag = rvError
331 rvNextAction%errorMsg='revolve::rvNextAction: insufficient allowed checkpoints'
332 ELSE
333 availCP = ourACP - ourRWCP
334 IF (availCP<1) THEN
335 rvNextAction%actionFlag = rvError
336 rvNextAction%errorMsg='revolve::rvNextAction: insufficient allowed checkpoints'
337 ELSE
338 reps = 0
339 range = 1
340 DO WHILE (range<ourCEnd-ourCStart)
341 reps = reps + 1
342 range = range*(reps+availCP)/reps
343 END DO
344 bino1 = range*reps/(availCP+reps)
345 IF (availCP>1) THEN
346 bino2 = bino1*availCP/(availCP+reps-1)
347 ELSE
348 bino2 = 1
349 END IF
350 IF (availCP==1) THEN
351 bino3 = 0
352 ELSE IF (availCP>2) THEN
353 bino3 = bino2*(availCP-1)/(availCP+reps-2)
354 ELSE
355 bino3 = 1
356 END IF
357 bino4 = bino2*(reps-1)/availCP
358 IF (availCP<3) THEN
359 bino5 = 0
360 ELSE IF (availCP>3) THEN
361 bino5 = bino3*(availCP-1)/reps
362 ELSE
363 bino5 = 1
364 END IF
365 IF (ourCEnd-ourCStart<=bino1+bino3) THEN
366 ourCStart = ourCStart + bino4
367 ELSE IF (ourCEnd-ourCStart>=range-bino5) THEN
368 ourCStart = ourCStart + bino1
369 ELSE
370 ourCStart = ourCEnd - bino2 - bino3
371 END IF
372 IF (ourCStart==prevCStart) THEN
373 ourCStart = prevCStart + 1
374 END IF
375 IF (ourCStart==ourSteps) THEN
376 ourNumFwd = ourNumFwd + ((ourCStart-1) - prevCStart)*ourBundle + ourTail
377 ELSE
378 ourNumFwd = ourNumFwd + (ourCStart - prevCStart)*ourBundle
379 END IF
380 rvNextAction%actionFlag = rvForward
381 END IF
382 END IF
383 rvNextAction%startIteration=prevCStart*ourBundle
384 IF (rvNextAction%actionFlag==rvFirstUTurn) THEN
385 rvNextAction%iteration=(ourCStart)*ourBundle+ourTail
386 ELSE IF (rvNextAction%actionFlag==rvUTurn) THEN
387 rvNextAction%iteration=(ourCStart+1)*ourBundle
388 ELSE
389 rvNextAction%iteration=(ourCStart)*ourBundle
390 END IF
391 IF (rvNextAction%actionFlag /= rvError) THEN
392 IF (ourVerbosity>2) THEN
393 SELECT CASE( rvNextAction%actionFlag)
394 CASE (rvForward)
395 WRITE (*,FMT='(A,I8,A,I8,A)') ' run forward iterations [', &
396 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'
397 CASE (rvRestore)
398 WRITE (*,FMT='(A,I8)') ' restore input of iteration ',&
399 rvNextAction%iteration
400 CASE (rvFirstUTurn)
401 WRITE (*,FMT='(A,I8,A,I8,A)') ' 1st uturn for iterations [',&
402 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'
403 CASE(rvUTurn)
404 WRITE (*,FMT='(A,I8,A,I8,A)') ' uturn for iterations [',&
405 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'
406 END SELECT
407 END IF
408 IF ((ourVerbosity>1) .AND. (rvNextAction%actionFlag == rvStore)) THEN
409 WRITE (*,FMT='(A,I8)') ' store input of iteration ',&
410 rvNextAction%iteration
411 END IF
412 END IF
413 rvNextAction%cpNum=ourRWCP
414 END FUNCTION rvNextAction
415
416 !--------------------------------------------------------------------*
417 !> estimates the number of checkpoints required; equivalent to `adjust` in Alg. 799
418 !! @param steps is the number of iterations
419 !! @param bundle is optional; detaults to 1, if specified indicates the number of iterations bundled in one tape/adjoint sweep
420 !! @return the number of checkpoints such that the growth in spatial complexity is balanced with the growth in temporal complexity
421 !!
422 !! this method does not change the internal state and does not require \ref rvInit
423 FUNCTION rvGuess(steps,bundle)
424 IMPLICIT NONE
425 INTEGER, INTENT(IN) :: steps, bundle
426 OPTIONAL :: bundle
427 INTEGER :: reps, s, checkpoints, b, tail, bSteps
428 INTEGER :: rvGuess
429 b=1
430 bSteps=steps
431 IF (present(bundle)) THEN
432 b=bundle
433 END IF
434 IF (steps<1) THEN
435 WRITE (*,fmt=*) 'revolve::rvGuess: error: steps < 1'
436 rvGuess = -1
437 ELSE IF (b<1) THEN
438 WRITE (*,fmt=*) 'revolve::rvGuess: error: bundle < 1'
439 rvGuess = -1
440 ELSE
441 IF (b .gt. 1) THEN
442 tail=modulo(bSteps,b)
443 bSteps=bSteps/b
444 IF (tail>0) THEN
445 bSteps=bSteps+1
446 END IF
447 END IF
448 IF (bSteps==1) THEN
449 rvGuess=0
450 ELSE
451 checkpoints = 1
452 reps = 1
453 s = 0
454 DO WHILE (chkRange(checkpoints+s,reps+s)>bSteps)
455 s = s - 1
456 END DO
457 DO WHILE (chkRange(checkpoints+s,reps+s)<bSteps)
458 s = s + 1
459 END DO
460 checkpoints = checkpoints + s
461 reps = reps + s
462 s = -1
463 DO WHILE (chkRange(checkpoints,reps)>=bSteps)
464 IF (checkpoints>reps) THEN
465 checkpoints = checkpoints - 1
466 s = 0
467 ELSE
468 reps = reps - 1
469 s = 1
470 END IF
471 END DO
472 IF (s==0) THEN
473 checkpoints = checkpoints + 1
474 END IF
475 IF (s==1) reps = reps + 1
476 rvGuess = checkpoints
477 END IF
478 END IF
479 END FUNCTION rvGuess
480
481 !--------------------------------------------------------------------*
482 !> computes the run time overhead factor; equivalent to `expense` in Alg. 799
483 !! @param steps is the number of iterations
484 !! @param checkpoints is the number of allowed checkpoints
485 !! @param bundle is optional; detaults to 1, if specified indicates the number of iterations bundled in one tape/adjoint sweep
486 !! @return the estimated runtime overhead factor (does not account for the time needed to write checkpoints)
487 !!
488 !! this method does not change the internal state and does not require \ref rvInit
489 FUNCTION rvFactor(steps,checkpoints,bundle)
490 IMPLICIT NONE
491 INTEGER, INTENT(IN) :: checkpoints, steps, bundle
492 OPTIONAL :: bundle
493 INTEGER :: b, f
494 DOUBLE PRECISION :: rvFactor
495 b=1
496 IF (present(bundle)) THEN
497 b=bundle
498 END IF
499 f=forwdCount(steps,checkpoints,b)
500 IF (f==-1) THEN
501 WRITE (*,fmt=*) 'revolve::rvFactor: error returned by revolve::forwdCount'
502 rvFactor=-1
503 ELSE
504 rvFactor = dble(f)/steps
505 END IF
506 END FUNCTION rvFactor
507
508 !--------------------------------------------------------------------*
509 !> internal method not to be referenced by the user
510 FUNCTION chkRange(ss,tt)
511 IMPLICIT NONE
512 INTEGER :: ss, tt
513 DOUBLE PRECISION :: res
514 INTEGER :: i
515 INTEGER :: chkRange
516 res = 1.
517 IF (tt<0 .OR. ss<0) THEN
518 WRITE (*,fmt=*) 'revolve::chkRange: error: negative parameter '
519 chkRange = -1
520 ELSE
521 DO i = 1, tt
522 res = res*(ss+i)
523 res = res/i
524 IF (res>=2.0D0**31) EXIT
525 END DO
526 IF (res<2.0D0**31-2) THEN
527 chkRange = res
528 ELSE
529 chkRange = 2.0D0**31 - 3
530 WRITE (*,fmt=*) 'revolve::chkRange: warning: returning maximal integer ',&
531 chkRange
532 END IF
533 END IF
534 END FUNCTION chkRange
535
536 !--------------------------------------------------------------------*
537
538 !> internal method not to be referenced by the user;
539 !> predicts the number of recomputation-from-checkpoint forwards steps (overhead)
540 FUNCTION forwdCount(steps,checkpoints,bundle)
541 IMPLICIT NONE
542 INTEGER, INTENT(IN) :: checkpoints, steps, bundle
543 INTEGER :: range, reps,s,tail
544 INTEGER :: forwdCount
545 IF (checkpoints<0) THEN
546 WRITE (*,fmt=*) 'revolve::forwdCount: error: checkpoints < 0'
547 forwdCount = -1
548 ELSE IF (steps<1) THEN
549 WRITE (*,fmt=*) 'revolve::forwdCount: error: steps < 1'
550 forwdCount = -1
551 ELSE IF (bundle<1) THEN
552 WRITE (*,fmt=*) 'revolve::forwdCount: error: bundle < 1'
553 forwdCount = -1
554 ELSE
555 s=steps
556 IF (bundle .gt. 1) THEN
557 tail=modulo(s,bundle)
558 s=s/bundle
559 IF (tail>0) THEN
560 s=s+1
561 END IF
562 END IF
563 IF (s==1) THEN
564 forwdCount = 0
565 ELSE IF (checkpoints==0) THEN
566 WRITE (*,fmt=*) &
567 'revolve::forwdCount: error: given inputs require checkpoints>0'
568 forwdCount = -1
569 ELSE
570 reps = 0
571 range = 1
572 DO WHILE (range<s)
573 reps = reps + 1
574 range = range*(reps+checkpoints)/reps
575 END DO
576 forwdCount = (reps*s - range*reps/(checkpoints+1))*bundle
577 END IF
578 END IF
579 END FUNCTION forwdCount
580
581 !--------------------------------------------------------------------*
582
583 END MODULE revolve

  ViewVC Help
Powered by ViewVC 1.1.22