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

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

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

revision 1.7 by cnh, Mon May 25 16:17:36 1998 UTC revision 1.10 by adcroft, Thu May 28 16:19:50 1998 UTC
# Line 2  C $Header$ Line 2  C $Header$
2    
3  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
4    
5        SUBROUTINE DYNAMICS(myThid)        SUBROUTINE DYNAMICS(myTime, myIter, myThid)
6  C     /==========================================================\  C     /==========================================================\
7  C     | SUBROUTINE DYNAMICS                                      |  C     | SUBROUTINE DYNAMICS                                      |
8  C     | o Controlling routine for the explicit part of the model |  C     | o Controlling routine for the explicit part of the model |
# Line 29  C     == Global variables === Line 29  C     == Global variables ===
29  #include "DYNVARS.h"  #include "DYNVARS.h"
30    
31  C     == Routine arguments ==  C     == Routine arguments ==
32    C     myTime - Current time in simulation
33    C     myIter - Current iteration number in simulation
34  C     myThid - Thread number for this instance of the routine.  C     myThid - Thread number for this instance of the routine.
35        INTEGER myThid        INTEGER myThid
36          _RL myTime
37          INTEGER myIter
38    
39  C     == Local variables  C     == Local variables
40  C     xA, yA                 - Per block temporaries holding face areas  C     xA, yA                 - Per block temporaries holding face areas
# Line 80  C                          into fVerTerm Line 84  C                          into fVerTerm
84        _RL pH    (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL pH    (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
85        _RL rhokm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86        _RL rhokp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87          _RL rhotmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88        _RL pSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL pSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89        _RL pSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL pSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90        _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
# Line 118  C     uninitialised but inert locations. Line 123  C     uninitialised but inert locations.
123          ENDDO          ENDDO
124          rhokm1(i,j)  = 0. _d 0          rhokm1(i,j)  = 0. _d 0
125          rhokp1(i,j)  = 0. _d 0          rhokp1(i,j)  = 0. _d 0
126            rhotmp(i,j)  = 0. _d 0
127         ENDDO         ENDDO
128        ENDDO        ENDDO
129    
# Line 167  C--     Update fields in top level accor Line 173  C--     Update fields in top level accor
173    
174  C--     Density of 1st level (below W(1)) reference to level 1  C--     Density of 1st level (below W(1)) reference to level 1
175          CALL FIND_RHO(          CALL FIND_RHO(
176       I     bi, bj, iMin, iMax, jMin, jMax, 1, 1, 'LINEAR',       I     bi, bj, iMin, iMax, jMin, jMax, 1, 1, eosType,
177       O     rhoKm1,       O     rhoKm1,
178       I     myThid )       I     myThid )
179  C--     Integrate hydrostatic balance for pH with BC of pH(z=0)=0  C--     Integrate hydrostatic balance for pH with BC of pH(z=0)=0
# Line 175  C--     Integrate hydrostatic balance fo Line 181  C--     Integrate hydrostatic balance fo
181       I      bi,bj,iMin,iMax,jMin,jMax,1,rhoKm1,rhoKm1,       I      bi,bj,iMin,iMax,jMin,jMax,1,rhoKm1,rhoKm1,
182       U      pH,       U      pH,
183       I      myThid )       I      myThid )
184            DO J=1-Oly,sNy+Oly
185             DO I=1-Olx,sNx+Olx
186              rhoKp1(I,J)=rhoKm1(I,J)
187             ENDDO
188            ENDDO
189    
190          DO K=2,Nz          DO K=2,Nz
191  C--     Update fields in Kth level according to tendency terms  C--     Update fields in Kth level according to tendency terms
192          CALL TIMESTEP(          CALL TIMESTEP(
193       I       bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myThid)       I       bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myThid)
194  C--     Density of K-1 level (above W(K)) reference to K level  C--     Density of K-1 level (above W(K)) reference to K-1 level
195          CALL FIND_RHO(  copt    CALL FIND_RHO(
196       I     bi, bj, iMin, iMax, jMin, jMax,  K-1, K, 'LINEAR',  copt I     bi, bj, iMin, iMax, jMin, jMax,  K-1, K-1, eosType,
197       O     rhoKm1,  copt O     rhoKm1,
198       I     myThid )  copt I     myThid )
199    C       rhoKm1=rhoKp1
200            DO J=1-Oly,sNy+Oly
201             DO I=1-Olx,sNx+Olx
202              rhoKm1(I,J)=rhoKp1(I,J)
203             ENDDO
204            ENDDO
205  C--     Density of K level (below W(K)) reference to K level  C--     Density of K level (below W(K)) reference to K level
206          CALL FIND_RHO(          CALL FIND_RHO(
207       I     bi, bj, iMin, iMax, jMin, jMax,  K, K, 'LINEAR',       I     bi, bj, iMin, iMax, jMin, jMax,  K, K, eosType,
208       O     rhoKp1,       O     rhoKp1,
209       I     myThid )       I     myThid )
210    C--     Density of K-1 level (above W(K)) reference to K level
211            CALL FIND_RHO(
212         I     bi, bj, iMin, iMax, jMin, jMax,  K-1, K, eosType,
213         O     rhotmp,
214         I     myThid )
215  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation
216          CALL CALC_ISOSLOPES(          CALL CALC_ISOSLOPES(
217       I            bi, bj, iMin, iMax, jMin, jMax, K,       I            bi, bj, iMin, iMax, jMin, jMax, K,
218       I            rhoKm1, rhoKp1,       I            rhoKm1, rhoKp1, rhotmp,
219       O            K13, K23, K33, KapGM,       O            K13, K23, K33, KapGM,
220       I            myThid )       I            myThid )
221  C--     Calculate static stability and mix where convectively unstable  C--     Calculate static stability and mix where convectively unstable
222          CALL CONVECT(          CALL CONVECT(
223       I      bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoKp1,myThid)       I      bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoKp1,
224         I      myTime,myIter,myThid)
225  C--     Density of K-1 level (above W(K)) reference to K-1 level  C--     Density of K-1 level (above W(K)) reference to K-1 level
226          CALL FIND_RHO(          CALL FIND_RHO(
227       I     bi, bj, iMin, iMax, jMin, jMax,  K-1, K-1, 'LINEAR',       I     bi, bj, iMin, iMax, jMin, jMax,  K-1, K-1, eosType,
228       O     rhoKm1,       O     rhoKm1,
229       I     myThid )       I     myThid )
230  C--     Density of K level (below W(K)) referenced to K level  C--     Density of K level (below W(K)) referenced to K level
231          CALL FIND_RHO(          CALL FIND_RHO(
232       I     bi, bj, iMin, iMax, jMin, jMax,  K, K, 'LINEAR',       I     bi, bj, iMin, iMax, jMin, jMax,  K, K, eosType,
233       O     rhoKp1,       O     rhoKp1,
234       I     myThid )       I     myThid )
235  C--     Integrate hydrostatic balance for pH with BC of pH(z=0)=0  C--     Integrate hydrostatic balance for pH with BC of pH(z=0)=0
# Line 233  C--      Get temporary terms used by ten Line 256  C--      Get temporary terms used by ten
256       I        myThid)       I        myThid)
257    
258  C--      Calculate accelerations in the momentum equations  C--      Calculate accelerations in the momentum equations
259           CALL CALC_MOM_RHS(           IF ( momStepping ) THEN
260       I        bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,            CALL CALC_MOM_RHS(
261       I        xA,yA,uTrans,vTrans,wTrans,maskC,       I         bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
262       I        pH,       I         xA,yA,uTrans,vTrans,wTrans,maskC,
263       U        aTerm,xTerm,cTerm,mTerm,pTerm,       I         pH,
264       U        fZon, fMer, fVerU, fVerV,       U         aTerm,xTerm,cTerm,mTerm,pTerm,
265       I        myThid)       U         fZon, fMer, fVerU, fVerV,
266         I         myThid)
267             ENDIF
268    
269  C--      Calculate active tracer tendencies  C--      Calculate active tracer tendencies
270           CALL CALC_GT(           IF ( tempStepping ) THEN
271       I        bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,            CALL CALC_GT(
272       I        xA,yA,uTrans,vTrans,wTrans,maskUp,       I         bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
273       I        K13,K23,K33,KapGM,       I         xA,yA,uTrans,vTrans,wTrans,maskUp,
274       U        aTerm,xTerm,fZon,fMer,fVerT,       I         K13,K23,K33,KapGM,
275       I        myThid)       U         aTerm,xTerm,fZon,fMer,fVerT,
276         I         myThid)
277             ENDIF
278  Cdbg     CALL CALC_GS(  Cdbg     CALL CALC_GS(
279  Cdbg I        bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,  Cdbg I        bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
280  Cdbg I        xA,yA,uTrans,vTrans,wTrans,maskUp,  Cdbg I        xA,yA,uTrans,vTrans,wTrans,maskUp,
# Line 265  Cdbg I        myThid) Line 292  Cdbg I        myThid)
292  !dbg &                         maxval(uVel(1:sNx,1:sNy,:,:,:))  !dbg &                         maxval(uVel(1:sNx,1:sNy,:,:,:))
293  !dbg  write(0,*) 'dynamics: V',minval(vVel(1:sNx,1:sNy,:,:,:)),  !dbg  write(0,*) 'dynamics: V',minval(vVel(1:sNx,1:sNy,:,:,:)),
294  !dbg &                         maxval(vVel(1:sNx,1:sNy,:,:,:))  !dbg &                         maxval(vVel(1:sNx,1:sNy,:,:,:))
295    !dbg  write(0,*) 'dynamics: K13',minval(K13(1:sNx,1:sNy,:)),
296    !dbg &                         maxval(K13(1:sNx,1:sNy,:))
297    !dbg  write(0,*) 'dynamics: K23',minval(K23(1:sNx,1:sNy,:)),
298    !dbg &                         maxval(K23(1:sNx,1:sNy,:))
299    !dbg  write(0,*) 'dynamics: K33',minval(K33(1:sNx,1:sNy,:)),
300    !dbg &                         maxval(K33(1:sNx,1:sNy,:))
301  !dbg  write(0,*) 'dynamics: gT',minval(gT(1:sNx,1:sNy,:,:,:)),  !dbg  write(0,*) 'dynamics: gT',minval(gT(1:sNx,1:sNy,:,:,:)),
302  !dbg &                         maxval(gT(1:sNx,1:sNy,:,:,:))  !dbg &                         maxval(gT(1:sNx,1:sNy,:,:,:))
303  !dbg  write(0,*) 'dynamics: T',minval(Theta(1:sNx,1:sNy,:,:,:)),  !dbg  write(0,*) 'dynamics: T',minval(Theta(1:sNx,1:sNy,:,:,:)),

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22