/[MITgcm]/MITgcm/pkg/mom_fluxform/mom_fluxform.F
ViewVC logotype

Diff of /MITgcm/pkg/mom_fluxform/mom_fluxform.F

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

revision 1.8 by jmc, Sun Jan 26 21:18:50 2003 UTC revision 1.18 by adcroft, Mon May 24 20:03:49 2004 UTC
# Line 25  C where ${\bf v}=(u,v,w)$ and $\tau$, th Line 25  C where ${\bf v}=(u,v,w)$ and $\tau$, th
25  C stresses as well as internal viscous stresses.  C stresses as well as internal viscous stresses.
26  CEOI  CEOI
27    
28  #include "CPP_OPTIONS.h"  #include "MOM_FLUXFORM_OPTIONS.h"
29    
30  CBOP  CBOP
31  C !ROUTINE: MOM_FLUXFORM  C !ROUTINE: MOM_FLUXFORM
# Line 33  C !ROUTINE: MOM_FLUXFORM Line 33  C !ROUTINE: MOM_FLUXFORM
33  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
34        SUBROUTINE MOM_FLUXFORM(        SUBROUTINE MOM_FLUXFORM(
35       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
36       I        phi_hyd,KappaRU,KappaRV,       I        dPhihydX,dPhiHydY,KappaRU,KappaRV,
37       U        fVerU, fVerV,       U        fVerU, fVerV,
38       I        myTime,myIter,myThid)       I        myTime,myIter,myThid)
39    
# Line 58  C  iMin,iMax,jMin,jMAx  :: loop ranges Line 58  C  iMin,iMax,jMin,jMAx  :: loop ranges
58  C  k                    :: vertical level  C  k                    :: vertical level
59  C  kUp                  :: =1 or 2 for consecutive k  C  kUp                  :: =1 or 2 for consecutive k
60  C  kDown                :: =2 or 1 for consecutive k  C  kDown                :: =2 or 1 for consecutive k
61  C  phi_hyd              :: hydrostatic pressure (perturbation)  C  dPhiHydX,Y           :: Gradient (X & Y dir.) of Hydrostatic Potential
62  C  KappaRU              :: vertical viscosity  C  KappaRU              :: vertical viscosity
63  C  KappaRV              :: vertical viscosity  C  KappaRV              :: vertical viscosity
64  C  fVerU                :: vertical flux of U, 2 1/2 dim for pipe-lining  C  fVerU                :: vertical flux of U, 2 1/2 dim for pipe-lining
# Line 68  C  myIter               :: current time- Line 68  C  myIter               :: current time-
68  C  myThid               :: thread number  C  myThid               :: thread number
69        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
70        INTEGER k,kUp,kDown        INTEGER k,kUp,kDown
71        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72          _RL dPhiHydY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
74        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
75        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 121  C     uDudxFac, AhDudxFac, etc ... indiv Line 122  C     uDudxFac, AhDudxFac, etc ... indiv
122        _RL  vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123        _RL  rTransU(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  rTransU(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124        _RL  rTransV(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  rTransV(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125          _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126          _RL viscAhD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127          _RL viscAhZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128          _RL viscA4D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129          _RL viscA4Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130          _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131          _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132          _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133          _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134  C     I,J,K - Loop counters  C     I,J,K - Loop counters
135  C     rVelMaskOverride - Factor for imposing special surface boundary conditions  C     rVelMaskOverride - Factor for imposing special surface boundary conditions
136  C                        ( set according to free-surface condition ).  C                        ( set according to free-surface condition ).
# Line 154  C     xxxFac - On-off tracer parameters Line 164  C     xxxFac - On-off tracer parameters
164        INTEGER km1,kp1        INTEGER km1,kp1
165        _RL wVelBottomOverride        _RL wVelBottomOverride
166        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
       _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
167  CEOP  CEOP
168    
169        km1=MAX(1,k-1)        km1=MAX(1,k-1)
# Line 178  C     Initialise intermediate terms Line 187  C     Initialise intermediate terms
187          fMer(i,j) = 0.          fMer(i,j) = 0.
188          rTransU(i,j) = 0.          rTransU(i,j) = 0.
189          rTransV(i,j) = 0.          rTransV(i,j) = 0.
190            strain(i,j) = 0.
191            tension(i,j) = 0.
192         ENDDO         ENDDO
193        ENDDO        ENDDO
194    
# Line 252  C     Calculate velocity field "volume t Line 263  C     Calculate velocity field "volume t
263         ENDDO         ENDDO
264        ENDDO        ENDDO
265    
266        CALL MOM_CALC_KE(bi,bj,k,uFld,vFld,KE,myThid)        CALL MOM_CALC_KE(bi,bj,k,3,uFld,vFld,KE,myThid)
267    
268    c     IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN
269             CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
270         O                         tension,
271         I                         myThid)
272             CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
273         O                        strain,
274         I                        myThid)
275    c     ENDIF
276    
277  C---  First call (k=1): compute vertical adv. flux fVerU(kUp) & fVerV(kUp)  C---  First call (k=1): compute vertical adv. flux fVerU(kUp) & fVerV(kUp)
278        IF (momAdvection.AND.k.EQ.1) THEN        IF (momAdvection.AND.k.EQ.1) THEN
# Line 288  C---  Calculate vertical transports (at Line 308  C---  Calculate vertical transports (at
308       I                       myTime, myIter, myThid)       I                       myTime, myIter, myThid)
309        ENDIF        ENDIF
310    
311    c     IF (momViscosity) THEN
312    c    &  CALL MOM_CALC_VISCOSITY(bi,bj,k,
313    c    I                         uFld,vFld,
314    c    O                         viscAhD,viscAhZ,myThid)
315    
316  C---- Zonal momentum equation starts here  C---- Zonal momentum equation starts here
317    
318  C     Bi-harmonic term del^2 U -> v4F  C     Bi-harmonic term del^2 U -> v4F
319        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
320       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
321    
322  C---  Calculate mean and eddy fluxes between cells for zonal flow.  C---  Calculate mean and eddy fluxes between cells for zonal flow.
# Line 325  C     Laplacian and bi-harmonic term Line 349  C     Laplacian and bi-harmonic term
349       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)
350    
351  C     Combine fluxes -> fMer  C     Combine fluxes -> fMer
352        DO j=jMin,jMax        DO j=jMin,jMax+1
353         DO i=iMin,iMax         DO i=iMin,iMax
354          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)
355         ENDDO         ENDDO
# Line 348  C     Combine fluxes Line 372  C     Combine fluxes
372         ENDDO         ENDDO
373        ENDDO        ENDDO
374    
 C---  Hydrostatic term ( -1/rhoConst . dphi/dx )  
       IF (momPressureForcing) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pf(i,j) = - _recip_dxC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i-1,j,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
375  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
376        DO j=jMin,jMax        DO j=jMin,jMax
377         DO i=iMin,iMax         DO i=iMin,iMax
# Line 373  C--   Tendency is minus divergence of th Line 387  C--   Tendency is minus divergence of th
387       &   +fMer(i,j+1)          - fMer(i  ,j)       &   +fMer(i,j+1)          - fMer(i  ,j)
388       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
389       &   )       &   )
390       & _PHM( +phxFac * pf(i,j) )       &  - phxFac*dPhiHydX(i,j)
391         ENDDO         ENDDO
392        ENDDO        ENDDO
393    
# Line 418  C-    No-slip BCs impose a drag at botto Line 432  C-    No-slip BCs impose a drag at botto
432         ENDDO         ENDDO
433        ENDIF        ENDIF
434    
435  C--   Forcing term  C--   Forcing term (moved to timestep.F)
436        IF (momForcing)  c     IF (momForcing)
437       &  CALL EXTERNAL_FORCING_U(  c    &  CALL EXTERNAL_FORCING_U(
438       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
439       I     myTime,myThid)  c    I     myTime,myThid)
440    
441  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
442        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
# Line 454  C--   Set du/dt on boundaries to zero Line 468  C--   Set du/dt on boundaries to zero
468  C---- Meridional momentum equation starts here  C---- Meridional momentum equation starts here
469    
470  C     Bi-harmonic term del^2 V -> v4F  C     Bi-harmonic term del^2 V -> v4F
471        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
472       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
473    
474  C---  Calculate mean and eddy fluxes between cells for meridional flow.  C---  Calculate mean and eddy fluxes between cells for meridional flow.
# Line 471  C     Laplacian and bi-harmonic terms -> Line 485  C     Laplacian and bi-harmonic terms ->
485    
486  C     Combine fluxes -> fZon  C     Combine fluxes -> fZon
487        DO j=jMin,jMax        DO j=jMin,jMax
488         DO i=iMin,iMax         DO i=iMin,iMax+1
489          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)
490         ENDDO         ENDDO
491        ENDDO        ENDDO
# Line 510  C     Combine fluxes -> fVerV Line 524  C     Combine fluxes -> fVerV
524         ENDDO         ENDDO
525        ENDDO        ENDDO
526    
 C---  Hydorstatic term (-1/rhoConst . dphi/dy )  
       IF (momPressureForcing) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pF(i,j) = -_recip_dyC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i,j-1,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
527  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
528        DO j=jMin,jMax        DO j=jMin,jMax
529         DO i=iMin,iMax         DO i=iMin,iMax
# Line 535  C--   Tendency is minus divergence of th Line 539  C--   Tendency is minus divergence of th
539       &   +fMer(i,j  )          - fMer(i,j-1)       &   +fMer(i,j  )          - fMer(i,j-1)
540       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
541       &   )       &   )
542       & _PHM( +phyFac*pf(i,j) )       &  - phyFac*dPhiHydY(i,j)
543         ENDDO         ENDDO
544        ENDDO        ENDDO
545    
# Line 580  C-    No-slip BCs impose a drag at botto Line 584  C-    No-slip BCs impose a drag at botto
584         ENDDO         ENDDO
585        ENDIF        ENDIF
586    
587  C--   Forcing term  C--   Forcing term (moved to timestep.F)
588        IF (momForcing)  c     IF (momForcing)
589       & CALL EXTERNAL_FORCING_V(  c    & CALL EXTERNAL_FORCING_V(
590       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
591       I     myTime,myThid)  c    I     myTime,myThid)
592    
593  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
594        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
# Line 614  C--   Set dv/dt on boundaries to zero Line 618  C--   Set dv/dt on boundaries to zero
618    
619  C--   Coriolis term  C--   Coriolis term
620  C     Note. As coded here, coriolis will not work with "thin walls"  C     Note. As coded here, coriolis will not work with "thin walls"
621  #ifdef INCLUDE_CD_CODE  c     IF (useCDscheme) THEN
622        CALL MOM_CDSCHEME(bi,bj,k,phi_hyd,myThid)  c       CALL MOM_CDSCHEME(bi,bj,k,dPhiHydX,dPhiHydY,myThid)
623  #else  c     ELSE
624        CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)        IF (.NOT.useCDscheme) THEN
625        DO j=jMin,jMax          CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)
626         DO i=iMin,iMax          DO j=jMin,jMax
627          gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)           DO i=iMin,iMax
628         ENDDO            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
629        ENDDO           ENDDO
630        CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)          ENDDO
631        DO j=jMin,jMax          CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)
632         DO i=iMin,iMax          DO j=jMin,jMax
633          gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)           DO i=iMin,iMax
634         ENDDO            gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
635        ENDDO           ENDDO
636  #endif /* INCLUDE_CD_CODE */          ENDDO
637          ENDIF
638    
639        IF (nonHydrostatic.OR.quasiHydrostatic) THEN        IF (nonHydrostatic.OR.quasiHydrostatic) THEN
640         CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)         CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
641         DO j=jMin,jMax         DO j=jMin,jMax

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22