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

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

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

revision 1.2 by utke, Sat Mar 9 17:17:39 2013 UTC revision 1.3 by jmc, Fri May 17 20:57:12 2013 UTC
# Line 17  Line 17 
17  MODULE revolve  MODULE revolve
18    IMPLICIT NONE    IMPLICIT NONE
19    
20    PUBLIC :: rvInit, rvVerbose, rvNextAction, rvGuess, rvFactor, &    PUBLIC :: rvInit, rvVerbose, rvNextAction, rvGuess, rvFactor, &
21  rvStore, rvRestore, rvForward, rvFirstUTurn, rvUTurn, rvDone, rvError  rvStore, rvRestore, rvForward, rvFirstUTurn, rvUTurn, rvDone, rvError
22    
23    PRIVATE :: &    PRIVATE :: &
24  ourSteps, ourACP, ourCStart, ourCEnd, ourVerbosity, &  ourSteps, ourACP, ourCStart, ourCEnd, ourVerbosity, &
25  ourNumFwd , ourNumInv, ourNumStore, ourRWCP, ourPrevCEnd, ourFirstUTurned, &    ourNumFwd , ourNumInv, ourNumStore, ourRWCP, ourPrevCEnd, ourFirstUTurned, &
26  chkRange, forwdCount  chkRange, forwdCount
27    
28    !> store a checkpoint now    !> store a checkpoint now
29    !! equivalent to TAKESHOT in Alg. 799    !! equivalent to TAKESHOT in Alg. 799
30    INTEGER, PARAMETER :: rvStore      =1    INTEGER, PARAMETER :: rvStore      =1
31    
32    !> restore a checkpoint now    !> restore a checkpoint now
33    !! equivalent to RESTORE in Alg. 799    !! equivalent to RESTORE in Alg. 799
# Line 93  chkRange, forwdCount Line 93  chkRange, forwdCount
93       !> if an error has occurred `actionFlag` will be set to `rvError` and this will contain an error message       !> if an error has occurred `actionFlag` will be set to `rvError` and this will contain an error message
94       CHARACTER(80) :: errorMsg       CHARACTER(80) :: errorMsg
95    END TYPE rvAction    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;    !> 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];    !! note that the iterations are expected to range in [0, ourSteps-1];
99    !!    !!
# Line 183  CONTAINS Line 183  CONTAINS
183      CHARACTER(*), INTENT(OUT) :: errorMsg      CHARACTER(*), INTENT(OUT) :: errorMsg
184      type(rvAction), optional :: anActionInstance      type(rvAction), optional :: anActionInstance
185      INTEGER, INTENT(IN), optional :: bundle      INTEGER, INTENT(IN), optional :: bundle
186      INTEGER :: predFwdCnt ! predicted forward count      INTEGER :: predFwdCnt ! predicted forward count
187      rvInit = .TRUE.      rvInit = .TRUE.
188      errorMsg ='none'      errorMsg ='none'
189      IF (present(anActionInstance)) THEN      IF (present(anActionInstance)) THEN
# Line 204  CONTAINS Line 204  CONTAINS
204      ELSEIF (checkpoints<0) THEN      ELSEIF (checkpoints<0) THEN
205         rvInit=.FALSE.         rvInit=.FALSE.
206         errorMsg = 'revolve::rvInit: negative checkpoints'         errorMsg = 'revolve::rvInit: negative checkpoints'
207      ELSE      ELSE
208         ourCStart       = 0         ourCStart       = 0
209         ourSteps        = steps         ourSteps        = steps
210         IF (ourBundle .gt. 1) THEN         IF (ourBundle .gt. 1) THEN
# Line 218  CONTAINS Line 218  CONTAINS
218         END IF         END IF
219         ourCEnd         = ourSteps         ourCEnd         = ourSteps
220         ourACP          = checkpoints         ourACP          = checkpoints
221         ourNumFwd       = 0         ourNumFwd       = 0
222         ourNumInv       = 0         ourNumInv       = 0
223         ourNumStore     = 0         ourNumStore     = 0
224         ourRWCP         = -1         ourRWCP         = -1
225         ourPrevCEnd     = 0         ourPrevCEnd     = 0
226         ourFirstUTurned = .FALSE.         ourFirstUTurned = .FALSE.
227    
228         IF (ALLOCATED(ourStepOf)) THEN         IF (ALLOCATED(ourStepOf)) THEN
# Line 252  CONTAINS Line 252  CONTAINS
252    !> method to set the verbosity to a level in [0-3] as described for `ourVerbosity`    !> method to set the verbosity to a level in [0-3] as described for `ourVerbosity`
253    SUBROUTINE rvVerbose(level)    SUBROUTINE rvVerbose(level)
254      IMPLICIT NONE      IMPLICIT NONE
255      INTEGER, INTENT(IN) :: level      INTEGER, INTENT(IN) :: level
256      ourVerbosity=level      ourVerbosity=level
257    END SUBROUTINE rvVerbose    END SUBROUTINE rvVerbose
258    
# Line 273  CONTAINS Line 273  CONTAINS
273    
274      INTEGER :: range      INTEGER :: range
275      INTEGER :: reps      INTEGER :: reps
276      INTEGER :: i      INTEGER :: i
277        INTEGER :: ourRWCPinBd
278      type(rvAction) :: rvNextAction      type(rvAction) :: rvNextAction
279      IF (ourNumInv==0) THEN      IF (ourNumInv==0) THEN
280         ! first invocation         ! first invocation
# Line 284  CONTAINS Line 285  CONTAINS
285      END IF      END IF
286      prevCStart = ourCStart      prevCStart = ourCStart
287      ourNumInv = ourNumInv + 1      ourNumInv = ourNumInv + 1
288        ! make sure ourRWCPinBd stay within bounds of array ourStepOf:
289        ourRWCPinBd = MIN( MAX( ourRWCP, 0 ), ourACP )
290      IF ((ourCEnd-ourCStart)==0) THEN      IF ((ourCEnd-ourCStart)==0) THEN
291         ! nothing in current subrange         ! nothing in current subrange
292         IF ((ourRWCP==(-1)) .OR. (ourCStart==ourStepOf(0))) THEN         IF ((ourRWCP==(-1)) .OR. (ourCStart==ourStepOf(0))) THEN
# Line 302  CONTAINS Line 305  CONTAINS
305          ELSE          ELSE
306             ourCStart = ourStepOf(ourRWCP)             ourCStart = ourStepOf(ourRWCP)
307             ourPrevCEnd = ourCEnd             ourPrevCEnd = ourCEnd
308             rvNextAction%actionFlag = rvRestore             rvNextAction%actionFlag = rvRestore
309          END IF          END IF
310       ELSE IF ((ourCEnd-ourCStart)==1) THEN       ELSE IF ((ourCEnd-ourCStart)==1) THEN
311          ourCEnd = ourCEnd - 1          ourCEnd = ourCEnd - 1
# Line 314  CONTAINS Line 317  CONTAINS
317          ELSE          ELSE
318             rvNextAction%actionFlag = rvUTurn             rvNextAction%actionFlag = rvUTurn
319          END IF          END IF
320       ELSE IF ((ourRWCP==(-1)) .OR. (ourStepOf(ourRWCP)/=ourCStart)) THEN       ELSE IF ((ourRWCP==(-1)) .OR. (ourStepOf(ourRWCPinBd)/=ourCStart)) THEN
321          ourRWCP = ourRWCP + 1          ourRWCP = ourRWCP + 1
322          IF (ourRWCP+1>ourACP) THEN          IF (ourRWCP+1>ourACP) THEN
323             rvNextAction%actionFlag = rvError             rvNextAction%actionFlag = rvError
# Line 400  CONTAINS Line 403  CONTAINS
403              CASE (rvFirstUTurn)              CASE (rvFirstUTurn)
404                 WRITE (*,FMT='(A,I8,A,I8,A)') ' 1st uturn for iterations  [',&                 WRITE (*,FMT='(A,I8,A,I8,A)') ' 1st uturn for iterations  [',&
405                 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'                 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'
406              CASE(rvUTurn)                    CASE(rvUTurn)
407                 WRITE (*,FMT='(A,I8,A,I8,A)') ' uturn for iterations      [',&                 WRITE (*,FMT='(A,I8,A,I8,A)') ' uturn for iterations      [',&
408                 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'                 rvNextAction%startIteration, ',', rvNextAction%iteration-1,']'
409              END SELECT              END SELECT

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.3

  ViewVC Help
Powered by ViewVC 1.1.22