/[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.30 by cnh, Thu Aug 20 20:05:01 1998 UTC revision 1.31 by cnh, Sat Aug 22 17:51:08 1998 UTC
# Line 62  C                                      v Line 62  C                                      v
62  C     rhoK, rhoKM1   - Density at current level, level above and level below.  C     rhoK, rhoKM1   - Density at current level, level above and level below.
63  C     rhoKP1                                                                    C     rhoKP1                                                                  
64  C     buoyK, buoyKM1 - Buoyancy at current level and level above.  C     buoyK, buoyKM1 - Buoyancy at current level and level above.
65  C     phiHyd         - Hydrostatic part of the potential phi.  C     phiHyd         - Hydrostatic part of the potential phiHydi.
66  C                      In z coords phiHyd is the hydrostatic pressure anomaly  C                      In z coords phiHydiHyd is the hydrostatic pressure anomaly
67  C                      In p coords phiHyd is the geopotential surface height  C                      In p coords phiHydiHyd is the geopotential surface height
68  C                      anomaly.  C                      anomaly.
69  C     etaSurfX,      - Holds surface elevation gradient in X and Y.  C     etaSurfX,      - Holds surface elevation gradient in X and Y.
70  C     etaSurfY  C     etaSurfY
# Line 98  C                      into fVerTerm Line 98  C                      into fVerTerm
98        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
99        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
100        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
101        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
102        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103        _RL rhokp1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokp1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 107  C                      into fVerTerm Line 107  C                      into fVerTerm
107        _RL rhotmp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhotmp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108        _RL etaSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL etaSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109        _RL etaSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL etaSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110        _RL K13     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K13     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
111        _RL K23     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K23     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
112        _RL K33     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K33     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
113        _RL KapGM   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KapGM   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114        _RL KappaZT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nz)        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
115        _RL KappaZS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nz)        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
116    
117        INTEGER iMin, iMax        INTEGER iMin, iMax
118        INTEGER jMin, jMax        INTEGER jMin, jMax
# Line 134  C Line 134  C
134  C       "Calculation of Gs"  C       "Calculation of Gs"
135  C       ===================  C       ===================
136  C       This is where all the accelerations and tendencies (ie.  C       This is where all the accelerations and tendencies (ie.
137  C       physics, parameterizations etc...) are calculated  C       phiHydysics, parameterizations etc...) are calculated
138  C         rVel = sum_r ( div. u[n] )  C         rVel = sum_r ( div. u[n] )
139  C         rho = rho ( theta[n], salt[n] )  C         rho = rho ( theta[n], salt[n] )
140  C         b   = b(rho, theta)  C         b   = b(rho, theta)
# Line 184  C     uninitialised but inert locations. Line 184  C     uninitialised but inert locations.
184          pTerm(i,j)   = 0. _d 0          pTerm(i,j)   = 0. _d 0
185          fZon(i,j)    = 0. _d 0          fZon(i,j)    = 0. _d 0
186          fMer(i,j)    = 0. _d 0          fMer(i,j)    = 0. _d 0
187          DO K=1,nZ          DO K=1,Nr
188           pH (i,j,k)  = 0. _d 0           phiHyd (i,j,k)  = 0. _d 0
189           K13(i,j,k)  = 0. _d 0           K13(i,j,k)  = 0. _d 0
190           K23(i,j,k)  = 0. _d 0           K23(i,j,k)  = 0. _d 0
191           K33(i,j,k)  = 0. _d 0           K33(i,j,k)  = 0. _d 0
192           KappaZT(i,j,k) = 0. _d 0           KappaRT(i,j,k) = 0. _d 0
193             KappaRS(i,j,k) = 0. _d 0
194          ENDDO          ENDDO
195          rhoKM1 (i,j) = 0. _d 0          rhoKM1 (i,j) = 0. _d 0
196          rhok   (i,j) = 0. _d 0          rhok   (i,j) = 0. _d 0
# Line 232  C--     Set up work arrays that need val Line 233  C--     Set up work arrays that need val
233          jMax = sNy+OLy          jMax = sNy+OLy
234    
235          K = 1          K = 1
236          BOTTOM_LAYER = K .EQ. Nz          BOTTOM_LAYER = K .EQ. Nr
237    
238  C--     Calculate gradient of surface pressure  C--     Calculate gradient of surface pressure
239          CALL CALC_GRAD_ETA_SURF(          CALL CALC_GRAD_ETA_SURF(
# Line 276  C--     Calculate buoyancy Line 277  C--     Calculate buoyancy
277       I      bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,       I      bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,
278       O      buoyKm1,       O      buoyKm1,
279       I      myThid )       I      myThid )
280  C--     Integrate hydrostatic balance for pH with BC of pH(z=0)=0  C--     Integrate hydrostatic balance for phiHyd with BC of phiHyd(z=0)=0
281          CALL CALC_PHI_HYD(          CALL CALC_PHI_HYD(
282       I      bi,bj,iMin,iMax,jMin,jMax,K,buoyKm1,buoyKm1,       I      bi,bj,iMin,iMax,jMin,jMax,K,buoyKm1,buoyKm1,
283       U      phiHyd,       U      phiHyd,
284       I      myThid )       I      myThid )
285    
286          DO K=2,Nz          DO K=2,Nr
287           BOTTOM_LAYER = K .EQ. Nz           BOTTOM_LAYER = K .EQ. Nr
288           IF ( .NOT. BOTTOM_LAYER ) THEN           IF ( .NOT. BOTTOM_LAYER ) THEN
289  C--       Update fields in layer below according to tendency terms  C--       Update fields in layer below according to tendency terms
290            CALL CORRECTION_STEP(            CALL CORRECTION_STEP(
# Line 316  C--      Calculate buoyancy Line 317  C--      Calculate buoyancy
317       I       bi,bj,iMin,iMax,jMin,jMax,K,rhoK,       I       bi,bj,iMin,iMax,jMin,jMax,K,rhoK,
318       O       buoyK,       O       buoyK,
319       I       myThid )       I       myThid )
320  C--      Integrate hydrostatic balance for pH with BC of pH(z=0)=0  C--      Integrate hydrostatic balance for phiHyd with BC of phiHyd(z=0)=0
321           CALL CALC_PHI_HYD(           CALL CALC_PHI_HYD(
322       I        bi,bj,iMin,iMax,jMin,jMax,K,buoyKm1,buoyK,       I        bi,bj,iMin,iMax,jMin,jMax,K,buoyKm1,buoyK,
323       U        phiHyd,       U        phiHyd,
# Line 339  C--      Calculate iso-neutral slopes fo Line 340  C--      Calculate iso-neutral slopes fo
340           ENDDO           ENDDO
341          ENDDO ! K          ENDDO ! K
342    
343          DO K = Nz, 1, -1          DO K = Nr, 1, -1
344    
345           kM1  =max(1,k-1)   ! Points to level above k (=k-1)           kM1  =max(1,k-1)   ! Points to level above k (=k-1)
346           kUp  =1+MOD(k+1,2) ! Cycles through 1,2 to point to layer above           kUp  =1+MOD(k+1,2) ! Cycles through 1,2 to point to layer above
# Line 358  C--      Calculate the total vertical di Line 359  C--      Calculate the total vertical di
359           CALL CALC_DIFFUSIVITY(           CALL CALC_DIFFUSIVITY(
360       I        bi,bj,iMin,iMax,jMin,jMax,K,       I        bi,bj,iMin,iMax,jMin,jMax,K,
361       I        maskC,maskUp,KapGM,K33,       I        maskC,maskUp,KapGM,K33,
362       O        KappaZT,KappaZS,       O        KappaRT,KappaRS,
363       I        myThid)       I        myThid)
364  C--      Calculate accelerations in the momentum equations  C--      Calculate accelerations in the momentum equations
365           IF ( momStepping ) THEN           IF ( momStepping ) THEN
# Line 392  C--      Prediction step (step forward a Line 393  C--      Prediction step (step forward a
393       I       bi,bj,iMin,iMax,jMin,jMax,K,       I       bi,bj,iMin,iMax,jMin,jMax,K,
394       I       myThid)       I       myThid)
395  C--      Diagnose barotropic divergence of predicted fields  C--      Diagnose barotropic divergence of predicted fields
396           CALL CALC_DIV_G(           CALL CALC_DIV_GHAT(
397       I       bi,bj,iMin,iMax,jMin,jMax,K,       I       bi,bj,iMin,iMax,jMin,jMax,K,
398       I       xA,yA,       I       xA,yA,
399       I       myThid)       I       myThid)
# Line 412  C--      Cumulative diagnostic calculati Line 413  C--      Cumulative diagnostic calculati
413  C--     Implicit diffusion  C--     Implicit diffusion
414          IF (implicitDiffusion) THEN          IF (implicitDiffusion) THEN
415           CALL IMPLDIFF( bi, bj, iMin, iMax, jMin, jMax,           CALL IMPLDIFF( bi, bj, iMin, iMax, jMin, jMax,
416       I                  KappaZT,KappaZS,       I                  KappaRT,KappaRS,
417       I                  myThid )       I                  myThid )
418          ENDIF          ENDIF
419    
# Line 445  C     write(0,*) 'dynamics: gS ',minval( Line 446  C     write(0,*) 'dynamics: gS ',minval(
446  C    &                           maxval(gS(1:sNx,1:sNy,:,:,:))  C    &                           maxval(gS(1:sNx,1:sNy,:,:,:))
447  C     write(0,*) 'dynamics: S  ',minval(salt(1:sNx,1:sNy,:,:,:)),  C     write(0,*) 'dynamics: S  ',minval(salt(1:sNx,1:sNy,:,:,:)),
448  C    &                           maxval(salt(1:sNx,1:sNy,:,:,:))  C    &                           maxval(salt(1:sNx,1:sNy,:,:,:))
449  C     write(0,*) 'dynamics: pH ',minval(pH/(Gravity*Rhonil),mask=ph.NE.0.),  C     write(0,*) 'dynamics: phiHyd ',minval(phiHyd/(Gravity*Rhonil),mask=phiHyd.NE.0.),
450  C    &                           maxval(pH/(Gravity*Rhonil))  C    &                           maxval(phiHyd/(Gravity*Rhonil))
451    
452        RETURN        RETURN
453        END        END

Legend:
Removed from v.1.30  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22