Nbody6
 All Files Functions Variables
steps.f
Go to the documentation of this file.
1  SUBROUTINE steps(I1,I2)
2 *
3 *
4 * Initialization of time-steps & prediction variables.
5 * ----------------------------------------------------
6 *
7  include 'common6.h'
8  REAL*8 fdum(3)
9 *
10 *
11 * Set new steps and initialize prediction variables.
12  DO 40 i = i1,i2
13 *
14 * Include regular force in the irregular step (cf. Makino & SJA 1992).
15  DO 5 k = 1,3
16  fdum(k) = fi(k,i) + fr(k,i)
17  5 CONTINUE
18 *
19 * Determine irregular and regular steps by the general criterion.
20  dt = tstep(fdum,d1(1,i),d2(1,i),d3(1,i),etai)
21  dtr = tstep(fr(1,i),d1r(1,i),d2r(1,i),d3r(1,i),etar)
22 *
23 * Reduce irregular step for case of triple, quad, chain or merger.
24  IF (iphase.GE.4) dt = 0.5*dt
25 *
26 * Initialize the times and obtain discrete steps (block-step version).
27  t0(i) = time
28  t0r(i) = time
29 *
30 * Convert predicted step to nearest block time-step (truncated down).
31  CALL stepk(dt,dtn)
32  CALL stepk(dtr,dtrn)
33  IF (time.LE.0.0d0) THEN
34  step(i) = dtn
35  stepr(i) = dtrn
36  ELSE
37 * Reduce steps by factor 2 until commensurate with current time.
38  step(i) = dtn
39  stepr(i) = dtrn
40  iter = 0
41  10 IF (dmod(time,step(i)).NE.0.0d0) THEN
42  step(i) = 0.5d0*step(i)
43  iter = iter + 1
44  IF (iter.LT.16.OR.step(i).GT.dtk(40)) go to 10
45  step(i) = dtk(40)
46  WRITE (6,15) i, iter, time/step(i), dt, step(i)
47  15 FORMAT (' WARNING! I ITER T/STEP DT STEP ',
48  & i5,i4,f16.4,1p,2e9.1)
49  END IF
50  iter = 0
51  18 IF (dmod(time,stepr(i)).NE.0.0d0) THEN
52  stepr(i) = 0.5d0*stepr(i)
53  iter = iter + 1
54  IF (iter.LT.16.OR.stepr(i).GT.dtk(40)) go to 18
55  stepr(i) = dtk(40)
56  WRITE (6,20) i, iter, time/stepr(i), dtr, stepr(i)
57  20 FORMAT (' WARNING! I ITER T/STEPR DTR STEPR ',
58  & i5,i4,f16.4,1p,2e9.1)
59  END IF
60  END IF
61 *
62 * Reduce irregular step if STEPR < STEP.
63  25 IF (stepr(i).LT.step(i)) THEN
64  step(i) = 0.5d0*step(i)
65  go to 25
66  END IF
67 *
68 * Initialize or update array for new block times.
69  tnew(i) = t0(i) + step(i)
70 * IF (TIME.GT.0.0) THEN
71 * WRITE (7,28) I, NAME(I), TIME, DT, STEP(I), STEPR(I)
72 * 28 FORMAT (' STEPS: I NM TIME DT STEP DTR ',
73 * & 2I5,F12.6,1P,3E9.1)
74 * CALL FLUSH(7)
75 * END IF
76 *
77 * Set prediction variables (X0DOT set by START, KSREG or KSTERM).
78  DO 30 k = 1,3
79  x0(k,i) = x(k,i)
80  f(k,i) = 0.5d0*f(k,i)
81  fdot(k,i) = one6*fdot(k,i)
82  30 CONTINUE
83  40 CONTINUE
84 *
85  RETURN
86 *
87  END