/[MITgcm]/MITgcm/model/src/the_correction_step.F
ViewVC logotype

Diff of /MITgcm/model/src/the_correction_step.F

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

revision 1.1 by adcroft, Thu Jan 4 21:41:33 2001 UTC revision 1.1.2.3 by adcroft, Tue Jan 30 21:03:00 2001 UTC
# Line 0  Line 1 
1    C $Header$
2    C Tag $Name$
3    
4    #include "CPP_OPTIONS.h"
5    
6          SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid)
7    C     /==========================================================\
8    C     | SUBROUTINE THE_CORRECTION_STEP                           |
9    C     |==========================================================|
10    C     |                                                          |
11    C     | U*,V* (contained in gUnm1,gVnm1) have the surface        |
12    C     |    pressure gradient term added and the result stored in |
13    C     |    U,V (contained in uVel, vVel)                         |
14    C     |                                                          |
15    C     | T* (contained in gTnm1) is copied to T (theta)           |
16    C     |                                                          |
17    C     | S* (contained in gSnm1) is copied to S (salt)            |
18    C     |                                                          |
19    C     \==========================================================/
20          IMPLICIT NONE
21    
22    C     == Global variables ===
23    #include "SIZE.h"
24    #include "EEPARAMS.h"
25    #include "PARAMS.h"
26    #include "DYNVARS.h"
27    
28    C     == Routine arguments ==
29    C     myTime - Current time in simulation
30    C     myIter - Current iteration number in simulation
31    C     myThid - Thread number for this instance of the routine.
32          _RL myTime
33          INTEGER myIter
34          INTEGER myThid
35    
36    C     == Local variables
37          _RL etaSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
38          _RL etaSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39          INTEGER iMin,iMax
40          INTEGER jMin,jMax
41          INTEGER bi,bj
42          INTEGER k,i,j
43    
44          DO bj=myByLo(myThid),myByHi(myThid)
45           DO bi=myBxLo(myThid),myBxHi(myThid)
46    
47    C--     Set up work arrays that need valid initial values
48            DO j=1-OLy,sNy+OLy
49             DO i=1-OLx,sNx+OLx
50              etaSurfX(i,j)=0.
51              etaSurfY(i,j)=0.
52             ENDDO
53            ENDDO
54    
55    C       The arrays used for time stepping are cycled.
56    C
57    C       Tracers:
58    C                 T(n) = Gt(n-1)
59    C                 Gt(n-1) = Gt(n)
60    C       Momentum:
61    C                 V(n) = Gv(n-1) - dt * grad Eta
62    C                 Gv(n-1) = Gv(n)
63    C
64    C       Static stability is calculated and the tracers are
65    C       convective adjusted where statically unstable.
66    
67    C       Loop range: Gradients of Eta are evaluated so valid
68    C       range is all but first row and column in overlaps.
69            iMin = 1-OLx+1
70            iMax = sNx+OLx
71            jMin = 1-OLy+1
72            jMax = sNy+OLy
73    
74    C-      Calculate gradient of surface pressure
75            CALL CALC_GRAD_ETA_SURF(
76         I       bi,bj,iMin,iMax,jMin,jMax,
77         O       etaSurfX,etaSurfY,
78         I       myThid )
79    
80    C--     Loop over all layers, top to bottom
81            DO K=1,Nr
82    
83    C-        Update velocity fields:  V(n) = V** - dt * grad Eta
84              CALL CORRECTION_STEP(
85         I         bi,bj,iMin,iMax,jMin,jMax,K,
86         I         etaSurfX,etaSurfY,myTime,myThid )
87    
88    C-        Update tracer fields:  T(n) = T**, Gt(n-1) = Gt(n)
89              IF (tempStepping)
90         &      CALL CYCLE_TRACER(
91         I           bi,bj,iMin,iMax,jMin,jMax,K,
92         U           theta,gT,gTNm1,
93         I           myTime,myThid )
94              IF (saltStepping)
95         &      CALL CYCLE_TRACER(
96         I           bi,bj,iMin,iMax,jMin,jMax,K,
97         U           salt,gS,gSNm1,
98         I           myTime,myThid )
99    
100    #ifdef    ALLOW_OBCS
101    #ifdef ALLOW_AUTODIFF_TAMC
102    CADJ STORE uvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
103    CADJ STORE vvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
104    CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
105    CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
106    #endif /* ALLOW_AUTODIFF_TAMC */
107              IF (useOBCS) THEN
108                CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
109              ENDIF
110    #endif    /* ALLOW_OBCS */
111    
112    C--     End DO K=1,Nr
113            ENDDO
114    
115    C--     Convectively adjust new fields to be statically stable
116            CALL CONVECTIVE_ADJUSTMENT(
117         I       bi, bj, iMin, iMax, jMin, jMax,
118         I       myTime, myIter, myThid )
119    
120           ENDDO
121          ENDDO
122    
123          RETURN
124          END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.1.2.3

  ViewVC Help
Powered by ViewVC 1.1.22