/[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.1 - (show annotations) (download)
Sat Feb 23 04:24:42 2013 UTC (11 years, 2 months ago) by utke
Branch: MAIN
CVS Tags: checkpoint64e
revolve loop

1 MODULE revolve
2 IMPLICIT NONE
3
4 PUBLIC :: rvInit, rvVerbose, rvNextAction, rvGuess, rvFactor, &
5 rvStore, rvRestore, rvForward, rvFirstUTurn, rvUTurn, rvDone, rvError
6
7 PRIVATE :: &
8 ourSteps, ourACP, ourCStart, ourCEnd, ourVerbosity, &
9 ourNumFwd , ourNumInv, ourNumStore, ourRWCP, ourPrevCEnd, ourFirstUTurned, &
10 chkRange, forwdCount
11
12 ! possible actions
13 INTEGER, PARAMETER :: rvStore =1
14 INTEGER, PARAMETER :: rvRestore =2
15 INTEGER, PARAMETER :: rvForward =3
16 INTEGER, PARAMETER :: rvFirstUTurn =4
17 INTEGER, PARAMETER :: rvUTurn =5
18 INTEGER, PARAMETER :: rvDone =6
19 INTEGER, PARAMETER :: rvError =7
20
21 TYPE rvAction
22 INTEGER :: actionFlag = 0
23 INTEGER :: iteration = 0
24 INTEGER :: cpNum = 0
25 CHARACTER, dimension(80) :: errorMsg
26 END TYPE rvAction
27
28 INTEGER :: ourSteps = 0 ! number of steps
29 INTEGER :: ourACP = 0 ! allowed number of checkpoints
30 INTEGER :: ourCStart = 0 ! current subrange start
31 INTEGER :: ourCEnd = 0 ! current subrange end
32 INTEGER :: ourNumFwd = 0 ! count of forward steps
33 INTEGER :: ourNumInv = 0 ! count of invocations of rvNextAction
34 INTEGER :: ourNumStore = 0 ! number of stored checkpoints
35 INTEGER :: ourRWCP = -1! checkpoint currently (re)stored (first checkpoint is 0)
36 INTEGER :: ourPrevCEnd = 0 ! previous subrange end
37 LOGICAL :: ourFirstUturned = .FALSE. ! have we first for the first time
38 ! vector of step numbers indexed by checkpoint
39 INTEGER, DIMENSION(:), ALLOCATABLE :: ourStepOf
40
41 ! for debugging purposes:
42 ! 0 includes errors
43 ! 1 includes summary info
44 ! 2 includes iterations with checkpoints stored
45 ! 3 includes all action results
46 INTEGER :: ourVerbosity = 0
47
48 CONTAINS
49
50 !--------------------------------------------------------------------*
51
52 FUNCTION rvInit(steps,checkpoints,errorMsg,anActionInstance)
53 IMPLICIT NONE
54 LOGICAL :: rvInit
55 INTEGER, INTENT(IN) :: steps
56 INTEGER, INTENT(IN) :: checkpoints
57 CHARACTER ,dimension(:), INTENT(OUT) :: errorMsg
58 type(rvAction), optional :: anActionInstance
59 INTEGER :: predFwdCnt ! predicted forward count
60 rvInit = .TRUE.
61 errorMsg ='none'
62 IF (present(anActionInstance)) THEN
63 ! same as default init above
64 anActionInstance%actionFlag = 0
65 anActionInstance%iteration = 0
66 anActionInstance%cpNum = 0
67 END IF
68 IF (steps<0 .OR. checkpoints<0) THEN
69 rvInit=.FALSE.
70 errorMsg = 'revolve::rvInit: negative steps or checkpoints'
71 ELSE
72 ourCStart = 0
73 ourSteps = steps
74 ourCEnd = steps
75 ourACP = checkpoints
76 ourNumFwd = 0
77 ourNumInv = 0
78 ourNumStore = 0
79 ourRWCP = -1
80 ourPrevCEnd = 0
81 ourFirstUTurned = .FALSE.
82
83 IF (ALLOCATED(ourStepOf)) THEN
84 DEALLOCATE(ourStepOf)
85 END IF
86 IF(.NOT.ALLOCATED(ourStepOf)) THEN
87 ALLOCATE(ourStepOf(0:ourACP))
88 END IF
89
90 IF (ourVerbosity>0) THEN
91 predFwdCnt = forwdCount(ourCEnd-ourCStart,ourACP)
92 IF (predFwdCnt==-1) THEN
93 errorMsg='error in forwdCount'
94 RETURN
95 ELSE
96 WRITE (*,'(A)') 'prediction:'
97 WRITE (*,'(A,I7)') ' needed forward steps: ', predFwdCnt
98 WRITE (*,'(A,F8.4)') ' slowdown factor : ', dble(predFwdCnt)/(ourCEnd-ourCStart)
99 END IF
100 END IF
101 END IF
102 END FUNCTION rvInit
103
104 !--------------------------------------------------------------------*
105
106 SUBROUTINE rvVerbose(level)
107 IMPLICIT NONE
108 INTEGER, INTENT(IN) :: level
109 ourVerbosity=level
110 END SUBROUTINE rvVerbose
111
112 !--------------------------------------------------------------------*
113
114 FUNCTION rvNextAction()
115 IMPLICIT NONE
116 REAL :: bino1, bino2, bino3, bino4, bino5
117 INTEGER :: availCP ! available checkpoint slots
118 INTEGER :: prevCStart ! previous subrange start
119 INTEGER :: range !
120 INTEGER :: reps
121 INTEGER :: i
122 type(rvAction) :: rvNextAction
123 IF (ourNumInv==0) THEN
124 ! first invocation
125 DO i = 0, ourACP
126 ourStepOf(i) = 0
127 END DO
128 ourStepOf(0) = ourCStart - 1
129 END IF
130 ourNumInv = ourNumInv + 1
131 IF ((ourCEnd-ourCStart)==0) THEN
132 ! nothing in current subrange
133 IF ((ourRWCP==(-1)) .OR. (ourCStart==ourStepOf(0))) THEN
134 ! we are done
135 ourRWCP = ourRWCP - 1
136 IF (ourVerbosity>0) THEN
137 WRITE (*,'(A)') 'summary:'
138 WRITE (*,'(A,I8)') ' forward steps:', ourNumFwd
139 WRITE (*,'(A,I8)') ' CP stores :', ourNumStore
140 WRITE (*,'(A,I8)') ' invocations :', ourNumInv
141 END IF
142 rvNextAction%actionFlag = rvDone
143 ELSE
144 ourCStart = ourStepOf(ourRWCP)
145 ourPrevCEnd = ourCEnd
146 rvNextAction%actionFlag = rvRestore
147 END IF
148 ELSE IF ((ourCEnd-ourCStart)==1) THEN
149 ourCEnd = ourCEnd - 1
150 ourPrevCEnd = ourCEnd
151 IF ((ourRWCP>=0) .AND. (ourStepOf(ourRWCP)==ourCStart)) ourRWCP = ourRWCP - 1
152 IF (.NOT.ourFirstUTurned) THEN
153 rvNextAction%actionFlag = rvFirstUTurn
154 ourFirstUTurned = .TRUE.
155 ELSE
156 rvNextAction%actionFlag = rvUTurn
157 END IF
158 ELSE IF ((ourRWCP==(-1)) .OR. (ourStepOf(ourRWCP)/=ourCStart)) THEN
159 ourRWCP = ourRWCP + 1
160 IF (ourRWCP+1>ourACP) THEN
161 rvNextAction%actionFlag = rvError
162 rvNextAction%errorMsg='insufficient allowed checkpoints'
163 RETURN
164 ELSE
165 ourStepOf(ourRWCP) = ourCStart
166 ourNumStore = ourNumStore + 1
167 ourPrevCEnd = ourCEnd
168 rvNextAction%actionFlag = rvStore
169 END IF
170 ELSE IF ((ourPrevCEnd<ourCEnd) .AND. (ourACP==ourRWCP+1)) THEN
171 rvNextAction%actionFlag = rvError
172 rvNextAction%errorMsg='insufficient allowed checkpoints'
173 ELSE
174 prevCStart = ourCStart
175 availCP = ourACP - ourRWCP
176 IF (availCP<1) THEN
177 rvNextAction%actionFlag = rvError
178 rvNextAction%errorMsg='insufficient allowed checkpoints'
179 ELSE
180 reps = 0
181 range = 1
182 DO WHILE (range<ourCEnd-ourCStart)
183 reps = reps + 1
184 range = range*(reps+availCP)/reps
185 END DO
186 bino1 = range*reps/(availCP+reps)
187 IF (availCP>1) THEN
188 bino2 = bino1*availCP/(availCP+reps-1)
189 ELSE
190 bino2 = 1
191 END IF
192 IF (availCP==1) THEN
193 bino3 = 0
194 ELSE IF (availCP>2) THEN
195 bino3 = bino2*(availCP-1)/(availCP+reps-2)
196 ELSE
197 bino3 = 1
198 END IF
199 bino4 = bino2*(reps-1)/availCP
200 IF (availCP<3) THEN
201 bino5 = 0
202 ELSE IF (availCP>3) THEN
203 bino5 = bino3*(availCP-1)/reps
204 ELSE
205 bino5 = 1
206 END IF
207 IF (ourCEnd-ourCStart<=bino1+bino3) THEN
208 ourCStart = ourCStart + bino4
209 ELSE IF (ourCEnd-ourCStart>=range-bino5) THEN
210 ourCStart = ourCStart + bino1
211 ELSE
212 ourCStart = ourCEnd - bino2 - bino3
213 END IF
214 IF (ourCStart==prevCStart) THEN
215 ourCStart = prevCStart + 1
216 END IF
217 ourNumFwd = ourNumFwd + ourCStart - prevCStart
218 rvNextAction%actionFlag = rvForward
219 END IF
220 END IF
221 rvNextAction%iteration=ourCStart
222 IF (rvNextAction%actionFlag /= rvError .AND. rvNextAction%actionFlag /= rvDone) THEN
223 IF (ourVerbosity>2) THEN
224 SELECT CASE( rvNextAction%actionFlag)
225 CASE (rvForward)
226 WRITE (*,FMT='(A)',ADVANCE='NO') ' forward to :'
227 CASE (rvRestore)
228 WRITE (*,FMT='(A)',ADVANCE='NO') ' restore at :'
229 CASE (rvFirstUTurn)
230 WRITE (*,FMT='(A)',ADVANCE='NO') ' 1st uturn at:'
231 CASE(rvUTurn)
232 WRITE (*,FMT='(A)',ADVANCE='NO') ' uturn at :'
233 END SELECT
234 END IF
235 IF (ourVerbosity>1) THEN
236 IF (rvNextAction%actionFlag == rvStore) THEN
237 WRITE (*,FMT='(A)',ADVANCE='NO') ' store at :'
238 END IF
239 WRITE (*,'(I8)') rvNextAction%iteration
240 END IF
241 END IF
242 rvNextAction%cpNum=ourRWCP
243 END FUNCTION rvNextAction
244
245 !--------------------------------------------------------------------*
246
247 FUNCTION rvGuess(steps)
248 IMPLICIT NONE
249 INTEGER :: steps
250 INTEGER :: reps, s, checkpoints
251 INTEGER :: rvGuess
252 checkpoints = 1
253 reps = 1
254 s = 0
255 DO WHILE (chkRange(checkpoints+s,reps+s)>steps)
256 s = s - 1
257 END DO
258 DO WHILE (chkRange(checkpoints+s,reps+s)<steps)
259 s = s + 1
260 END DO
261 checkpoints = checkpoints + s
262 reps = reps + s
263 s = -1
264 DO WHILE (chkRange(checkpoints,reps)>=steps)
265 IF (checkpoints>reps) THEN
266 checkpoints = checkpoints - 1
267 s = 0
268 ELSE
269 reps = reps - 1
270 s = 1
271 END IF
272 END DO
273 IF (s==0) THEN
274 checkpoints = checkpoints + 1
275 END IF
276 IF (s==1) reps = reps + 1
277 rvGuess = checkpoints
278 END FUNCTION rvGuess
279
280 !--------------------------------------------------------------------*
281
282 FUNCTION rvFactor(steps,checkpoints)
283 IMPLICIT NONE
284 INTEGER :: checkpoints, steps
285 DOUBLE PRECISION :: rvFactor
286 IF (checkpoints<1) THEN
287 WRITE (*,fmt=*) 'error occurs in RVFACTOR: CHECKPOINTS < 1'
288 rvFactor = -1
289 ELSE IF (checkpoints<1) THEN
290 WRITE (*,fmt=*) 'error occurs in RVFACTOR: CHECKPOINTS < 1'
291 rvFactor = -1
292 ELSE
293 rvFactor = dble(forwdCount(steps,checkpoints))
294 IF (rvFactor/=-1) rvFactor = rvFactor/steps
295 END IF
296 END FUNCTION rvFactor
297
298 !--------------------------------------------------------------------*
299
300 FUNCTION chkRange(ss,tt)
301 IMPLICIT NONE
302 INTEGER :: ss, tt
303 DOUBLE PRECISION :: res
304 INTEGER :: i
305 INTEGER :: chkRange
306 res = 1.
307 IF (tt<0 .OR. ss<0) THEN
308 WRITE (*,fmt=*) 'error in MAXRANGE: negative parameter '
309 chkRange = -1
310 ELSE
311 DO i = 1, tt
312 res = res*(ss+i)
313 res = res/i
314 IF (res>=2.0D0**31) EXIT
315 END DO
316 IF (res<2.0D0**31-2) THEN
317 chkRange = res
318 ELSE
319 chkRange = 2.0D0**31 - 3
320 WRITE (*,fmt=*) 'warning from MAXRANGE: returned maximal integer'
321 WRITE (*,fmt=*) chkRange
322 END IF
323 END IF
324 END FUNCTION chkRange
325
326 !--------------------------------------------------------------------*
327
328 FUNCTION forwdCount(steps,checkpoints)
329 IMPLICIT NONE
330 INTEGER :: checkpoints, steps
331 INTEGER :: range, reps
332 INTEGER :: forwdCount
333 IF (checkpoints<1) THEN
334 forwdCount = -1
335 ELSE
336 reps = 0
337 range = 1
338 DO WHILE (range<steps)
339 reps = reps + 1
340 range = range*(reps+checkpoints)/reps
341 END DO
342 forwdCount = reps*steps - range*reps/(checkpoints+1)
343 END IF
344 END FUNCTION forwdCount
345
346 !--------------------------------------------------------------------*
347
348 END MODULE revolve

  ViewVC Help
Powered by ViewVC 1.1.22