/[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.19 by cnh, Mon Jun 15 05:13:56 1998 UTC revision 1.25 by adcroft, Thu Jul 16 15:23:43 1998 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    
3  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
4    
5        SUBROUTINE DYNAMICS(myTime, myIter, myThid)        SUBROUTINE DYNAMICS(myTime, myIter, myThid)
6  C     /==========================================================\  C     /==========================================================\
# Line 203  C--     Set up work arrays that need val Line 203  C--     Set up work arrays that need val
203            K13(i,j,1) = 0. _d 0            K13(i,j,1) = 0. _d 0
204            K23(i,j,1) = 0. _d 0            K23(i,j,1) = 0. _d 0
205            K33(i,j,1) = 0. _d 0            K33(i,j,1) = 0. _d 0
206            KapGM(i,j) = 0. _d 0            KapGM(i,j) = GMkbackground
207           ENDDO           ENDDO
208          ENDDO          ENDDO
209    
# Line 223  C--     Calculate gradient of surface pr Line 223  C--     Calculate gradient of surface pr
223    
224  C--     Update fields in top level according to tendency terms  C--     Update fields in top level according to tendency terms
225          CALL CORRECTION_STEP(          CALL CORRECTION_STEP(
226       I       bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myThid)       I       bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myTime,myThid)
227    
228            IF ( .NOT. BOTTOM_LAYER ) THEN
229    C--      Update fields in layer below according to tendency terms
230             CALL CORRECTION_STEP(
231         I        bi,bj,iMin,iMax,jMin,jMax,K+1,pSurfX,pSurfY,myTime,myThid)
232            ENDIF
233    
234  C--     Density of 1st level (below W(1)) reference to level 1  C--     Density of 1st level (below W(1)) reference to level 1
235          CALL FIND_RHO(          CALL FIND_RHO(
# Line 258  C--     Integrate hydrostatic balance fo Line 264  C--     Integrate hydrostatic balance fo
264    
265           BOTTOM_LAYER = K .EQ. Nz           BOTTOM_LAYER = K .EQ. Nz
266    
267  C--      Update fields in Kth level according to tendency terms           IF ( .NOT. BOTTOM_LAYER ) THEN
268           CALL CORRECTION_STEP(  C--       Update fields in layer below according to tendency terms
269       I        bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myThid)            CALL CORRECTION_STEP(
270         I         bi,bj,iMin,iMax,jMin,jMax,K+1,pSurfX,pSurfY,myTime,myThid)
271             ENDIF
272    C--      Update fields in layer below according to tendency terms
273    C        CALL CORRECTION_STEP(
274    C    I        bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myTime,myThid)
275    
276  C--      Density of K level (below W(K)) reference to K level  C--      Density of K level (below W(K)) reference to K level
277           CALL FIND_RHO(           CALL FIND_RHO(
278       I      bi, bj, iMin, iMax, jMin, jMax,  K, K, eosType,       I      bi, bj, iMin, iMax, jMin, jMax,  K, K, eosType,
# Line 343  C--      Calculate active tracer tendenc Line 355  C--      Calculate active tracer tendenc
355           IF ( tempStepping ) THEN           IF ( tempStepping ) THEN
356            CALL CALC_GT(            CALL CALC_GT(
357       I         bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
358       I         xA,yA,uTrans,vTrans,wTrans,maskUp,       I         xA,yA,uTrans,vTrans,wTrans,maskUp,maskC,
359       I         K13,K23,KappaZT,KapGM,       I         K13,K23,KappaZT,KapGM,
360       U         aTerm,xTerm,fZon,fMer,fVerT,       U         aTerm,xTerm,fZon,fMer,fVerT,
361       I         myThid)       I         myThid)
# Line 351  C--      Calculate active tracer tendenc Line 363  C--      Calculate active tracer tendenc
363           IF ( saltStepping ) THEN           IF ( saltStepping ) THEN
364            CALL CALC_GS(            CALL CALC_GS(
365       I         bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
366       I         xA,yA,uTrans,vTrans,wTrans,maskUp,       I         xA,yA,uTrans,vTrans,wTrans,maskUp,maskC,
367       I         K13,K23,KappaZS,KapGM,       I         K13,K23,KappaZS,KapGM,
368       U         aTerm,xTerm,fZon,fMer,fVerS,       U         aTerm,xTerm,fZon,fMer,fVerS,
369       I         myThid)       I         myThid)
# Line 368  C--      Diagnose barotropic divergence Line 380  C--      Diagnose barotropic divergence
380       I       xA,yA,       I       xA,yA,
381       I       myThid)       I       myThid)
382    
383    C--      Cumulative diagnostic calculations (ie. time-averaging)
384    #ifdef ALLOW_DIAGNOSTICS
385             IF (taveFreq.GT.0.) THEN
386              CALL DO_TIME_AVERAGES(
387         I                           myTime, myIter, bi, bj, K, kUp, kDown,
388         I                           K13, K23, wVel, KapGM,
389         I                           myThid )
390             ENDIF
391    #endif
392    
393          ENDDO ! K          ENDDO ! K
394    
395  C--     Implicit diffusion  C--     Implicit diffusion
# Line 382  C--     Implicit diffusion Line 404  C--     Implicit diffusion
404    
405  C     write(0,*) 'dynamics: pS ',minval(cg2d_x(1:sNx,1:sNy,:,:)),  C     write(0,*) 'dynamics: pS ',minval(cg2d_x(1:sNx,1:sNy,:,:)),
406  C    &                           maxval(cg2d_x(1:sNx,1:sNy,:,:))  C    &                           maxval(cg2d_x(1:sNx,1:sNy,:,:))
407        write(0,*) 'dynamics: U  ',minval(uVel(1:sNx,1:sNy,1,:,:),mask=uVel(1:sNx,1:sNy,1,:,:).NE.0.),  C     write(0,*) 'dynamics: U  ',minval(uVel(1:sNx,1:sNy,1,:,:),mask=uVel(1:sNx,1:sNy,1,:,:).NE.0.),
408       &                           maxval(uVel(1:sNx,1:sNy,1,:,:))  C    &                           maxval(uVel(1:sNx,1:sNy,1,:,:),mask=uVel(1:sNx,1:sNy,1,:,:).NE.0.)
409        write(0,*) 'dynamics: V  ',minval(vVel(1:sNx,1:sNy,1,:,:),mask=vVel(1:sNx,1:sNy,1,:,:).NE.0.),  C     write(0,*) 'dynamics: V  ',minval(vVel(1:sNx,1:sNy,1,:,:),mask=vVel(1:sNx,1:sNy,1,:,:).NE.0.),
410       &                           maxval(vVel(1:sNx,1:sNy,1,:,:))  C    &                           maxval(vVel(1:sNx,1:sNy,1,:,:),mask=vVel(1:sNx,1:sNy,1,:,:).NE.0.)
411        write(0,*) 'dynamics: wVel(1) ',  C     write(0,*) 'dynamics: wVel(1) ',
412       &            minval(wVel(1:sNx,1:sNy,1),mask=wVel(1:sNx,1:sNy,1).NE.0.),  C    &            minval(wVel(1:sNx,1:sNy,1),mask=wVel(1:sNx,1:sNy,1).NE.0.),
413       &            maxval(wVel(1:sNx,1:sNy,1))  C    &            maxval(wVel(1:sNx,1:sNy,1),mask=wVel(1:sNx,1:sNy,1).NE.0.)
414        write(0,*) 'dynamics: wVel(2) ',  C     write(0,*) 'dynamics: wVel(2) ',
415       &            minval(wVel(1:sNx,1:sNy,2),mask=wVel(1:sNx,1:sNy,2).NE.0.),  C    &            minval(wVel(1:sNx,1:sNy,2),mask=wVel(1:sNx,1:sNy,2).NE.0.),
416       &            maxval(wVel(1:sNx,1:sNy,2))  C    &            maxval(wVel(1:sNx,1:sNy,2),mask=wVel(1:sNx,1:sNy,2).NE.0.)
417  cblk  write(0,*) 'dynamics: K13',minval(K13(1:sNx,1:sNy,:)),  cblk  write(0,*) 'dynamics: K13',minval(K13(1:sNx,1:sNy,:)),
418  cblk &                           maxval(K13(1:sNx,1:sNy,:))  cblk &                           maxval(K13(1:sNx,1:sNy,:))
419  cblk  write(0,*) 'dynamics: K23',minval(K23(1:sNx,1:sNy,:)),  cblk  write(0,*) 'dynamics: K23',minval(K23(1:sNx,1:sNy,:)),
# Line 406  C     write(0,*) 'dynamics: gS ',minval( Line 428  C     write(0,*) 'dynamics: gS ',minval(
428  C    &                           maxval(gS(1:sNx,1:sNy,:,:,:))  C    &                           maxval(gS(1:sNx,1:sNy,:,:,:))
429  C     write(0,*) 'dynamics: S  ',minval(salt(1:sNx,1:sNy,:,:,:)),  C     write(0,*) 'dynamics: S  ',minval(salt(1:sNx,1:sNy,:,:,:)),
430  C    &                           maxval(salt(1:sNx,1:sNy,:,:,:))  C    &                           maxval(salt(1:sNx,1:sNy,:,:,:))
431        write(0,*) 'dynamics: pH ',minval(pH/(Gravity*Rhonil),mask=ph.NE.0.),  C     write(0,*) 'dynamics: pH ',minval(pH/(Gravity*Rhonil),mask=ph.NE.0.),
432       &                           maxval(pH/(Gravity*Rhonil))  C    &                           maxval(pH/(Gravity*Rhonil))
433    
434        RETURN        RETURN
435        END        END

Legend:
Removed from v.1.19  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22