/[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.32 by mlosch, Tue Feb 7 11:46:18 2006 UTC revision 1.37 by jmc, Thu Jul 13 03:02:48 2006 UTC
# Line 31  CBOP Line 31  CBOP
31  C !ROUTINE: MOM_FLUXFORM  C !ROUTINE: MOM_FLUXFORM
32    
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        KappaRU, KappaRV,       I        KappaRU, KappaRV,
37       U        fVerU, fVerV,       U        fVerU, fVerV,
# Line 52  C     == Global variables == Line 52  C     == Global variables ==
52  #include "PARAMS.h"  #include "PARAMS.h"
53  #include "GRID.h"  #include "GRID.h"
54  #include "SURFACE.h"  #include "SURFACE.h"
55    #ifdef ALLOW_AUTODIFF_TAMC
56    # include "tamc.h"
57    # include "tamc_keys.h"
58    # include "MOM_FLUXFORM.h"
59    #endif
60    
61  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
62  C  bi,bj                :: tile indices  C  bi,bj                :: tile indices
# Line 93  C  fZon                 :: zonal fluxes Line 98  C  fZon                 :: zonal fluxes
98  C  fMer                 :: meridional fluxes  C  fMer                 :: meridional fluxes
99  C  fVrUp,fVrDw          :: vertical viscous fluxes at interface k-1 & k  C  fVrUp,fVrDw          :: vertical viscous fluxes at interface k-1 & k
100        INTEGER i,j        INTEGER i,j
101    #ifdef ALLOW_AUTODIFF_TAMC
102          INTEGER imomkey
103    #endif
104        _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105        _RL v4F(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL v4F(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106        _RL cF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL cF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 101  C  fVrUp,fVrDw          :: vertical visc Line 109  C  fVrUp,fVrDw          :: vertical visc
109        _RL fMer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fMer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110        _RL fVrUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fVrUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111        _RL fVrDw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fVrDw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112  C     afFacMom      - Tracer parameters for turning terms  C     afFacMom     :: Tracer parameters for turning terms on and off.
113  C     vfFacMom        on and off.  C     vfFacMom
114  C     pfFacMom        afFacMom - Advective terms  C     pfFacMom        afFacMom - Advective terms
115  C     cfFacMom        vfFacMom - Eddy viscosity terms  C     cfFacMom        vfFacMom - Eddy viscosity terms
116  C     mTFacMom        pfFacMom - Pressure terms  C     mtFacMom        pfFacMom - Pressure terms
117  C                     cfFacMom - Coriolis terms  C                     cfFacMom - Coriolis terms
118  C                     foFacMom - Forcing  C                     foFacMom - Forcing
119  C                     mTFacMom - Metric term  C                     mtFacMom - Metric term
120  C     uDudxFac, AhDudxFac, etc ... individual term parameters for switching terms off  C     uDudxFac, AhDudxFac, etc ... individual term parameters for switching terms off
121        _RS    hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS    hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RS  r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS  r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 137  C     uDudxFac, AhDudxFac, etc ... indiv Line 145  C     uDudxFac, AhDudxFac, etc ... indiv
145        _RL  ArDudrFac        _RL  ArDudrFac
146        _RL  fuFac        _RL  fuFac
147        _RL  mtFacU        _RL  mtFacU
148          _RL  mtNHFacU
149        _RL  uDvdxFac        _RL  uDvdxFac
150        _RL  AhDvdxFac        _RL  AhDvdxFac
151        _RL  vDvdyFac        _RL  vDvdyFac
# Line 145  C     uDudxFac, AhDudxFac, etc ... indiv Line 154  C     uDudxFac, AhDudxFac, etc ... indiv
154        _RL  ArDvdrFac        _RL  ArDvdrFac
155        _RL  fvFac        _RL  fvFac
156        _RL  mtFacV        _RL  mtFacV
157          _RL  mtNHFacV
158        _RL  sideMaskFac        _RL  sideMaskFac
159        LOGICAL bottomDragTerms,harmonic,biharmonic,useVariableViscosity        LOGICAL bottomDragTerms,harmonic,biharmonic,useVariableViscosity
160  CEOP  CEOP
161    
162    #ifdef ALLOW_AUTODIFF_TAMC
163              act0 = k - 1
164              max0 = Nr
165              act1 = bi - myBxLo(myThid)
166              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
167              act2 = bj - myByLo(myThid)
168              max2 = myByHi(myThid) - myByLo(myThid) + 1
169              act3 = myThid - 1
170              max3 = nTx*nTy
171              act4 = ikey_dynamics - 1
172              imomkey = (act0 + 1)
173         &                    + act1*max0
174         &                    + act2*max0*max1
175         &                    + act3*max0*max1*max2
176         &                    + act4*max0*max1*max2*max3
177    #endif /* ALLOW_AUTODIFF_TAMC */
178    
179  C     Initialise intermediate terms  C     Initialise intermediate terms
180        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
181         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 182  C     o U momentum equation Line 209  C     o U momentum equation
209        AhDudyFac    = vfFacMom*1.        AhDudyFac    = vfFacMom*1.
210        rVelDudrFac  = afFacMom*1.        rVelDudrFac  = afFacMom*1.
211        ArDudrFac    = vfFacMom*1.        ArDudrFac    = vfFacMom*1.
212        mTFacU       = mtFacMom*1.        mtFacU       = mtFacMom*1.
213          mtNHFacU     = 1.
214        fuFac        = cfFacMom*1.        fuFac        = cfFacMom*1.
215  C     o V momentum equation  C     o V momentum equation
216        uDvdxFac     = afFacMom*1.        uDvdxFac     = afFacMom*1.
# Line 191  C     o V momentum equation Line 219  C     o V momentum equation
219        AhDvdyFac    = vfFacMom*1.        AhDvdyFac    = vfFacMom*1.
220        rVelDvdrFac  = afFacMom*1.        rVelDvdrFac  = afFacMom*1.
221        ArDvdrFac    = vfFacMom*1.        ArDvdrFac    = vfFacMom*1.
222        mTFacV       = mtFacMom*1.        mtFacV       = mtFacMom*1.
223          mtNHFacV     = 1.
224        fvFac        = cfFacMom*1.        fvFac        = cfFacMom*1.
225    
226        IF (implicitViscosity) THEN        IF (implicitViscosity) THEN
# Line 273  C---  First call (k=1): compute vertical Line 302  C---  First call (k=1): compute vertical
302        IF (momAdvection.AND.k.EQ.1) THEN        IF (momAdvection.AND.k.EQ.1) THEN
303    
304  C-    Calculate vertical transports above U & V points (West & South face):  C-    Calculate vertical transports above U & V points (West & South face):
305    
306    #ifdef ALLOW_AUTODIFF_TAMC
307    # ifdef NONLIN_FRSURF
308    #  ifndef DISABLE_RSTAR_CODE
309    CADJ STORE dwtransc(:,:,bi,bj) =
310    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
311    CADJ STORE dwtransu(:,:,bi,bj) =
312    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
313    CADJ STORE dwtransv(:,:,bi,bj) =
314    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
315    #  endif
316    # endif /* NONLIN_FRSURF */
317    #endif /* ALLOW_AUTODIFF_TAMC */
318          CALL MOM_CALC_RTRANS( k, bi, bj,          CALL MOM_CALC_RTRANS( k, bi, bj,
319       O                        rTransU, rTransV,       O                        rTransU, rTransV,
320       I                        myTime, myIter, myThid)       I                        myTime, myIter, myThid)
# Line 390  C-    endif momAdvection. Line 432  C-    endif momAdvection.
432  C---  Calculate eddy fluxes (dissipation) between cells for zonal flow.  C---  Calculate eddy fluxes (dissipation) between cells for zonal flow.
433    
434  C     Bi-harmonic term del^2 U -> v4F  C     Bi-harmonic term del^2 U -> v4F
435          IF (biharmonic)          IF (biharmonic)
436       &  CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)       &  CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
437    
438  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon
# Line 434  C--   Tendency is minus divergence of th Line 476  C--   Tendency is minus divergence of th
476          ENDIF          ENDIF
477  #endif  #endif
478    
479  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
480          IF (no_slip_sides) THEN          IF (no_slip_sides) THEN
481  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
482           CALL MOM_U_SIDEDRAG(           CALL MOM_U_SIDEDRAG(
# Line 482  c    I     myTime,myThid) Line 524  c    I     myTime,myThid)
524    
525  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
526        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
527  C      o Non-hydrosatic metric terms  C      o Non-Hydrostatic (spherical) metric terms
528         CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)         CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
529         DO j=jMin,jMax         DO j=jMin,jMax
530          DO i=iMin,iMax          DO i=iMin,iMax
531           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtNHFacU*mT(i,j)
532          ENDDO          ENDDO
533         ENDDO         ENDDO
534        ENDIF        ENDIF
535        IF (usingSphericalPolarMTerms) THEN        IF ( usingSphericalPolarGrid .AND. metricTerms ) THEN
536    C      o Spherical polar grid metric terms
537         CALL MOM_U_METRIC_SPHERE(bi,bj,k,uFld,vFld,mT,myThid)         CALL MOM_U_METRIC_SPHERE(bi,bj,k,uFld,vFld,mT,myThid)
538         DO j=jMin,jMax         DO j=jMin,jMax
539          DO i=iMin,iMax          DO i=iMin,iMax
540           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtFacU*mT(i,j)
541          ENDDO          ENDDO
542         ENDDO         ENDDO
543        ENDIF        ENDIF
544        IF (usingCylindricalGrid) THEN        IF ( usingCylindricalGrid .AND. metricTerms ) THEN
545           CALL MOM_U_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)  C      o Cylindrical grid metric terms
546           DO j=jMin,jMax         CALL MOM_U_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
547            DO i=iMin,iMax         DO j=jMin,jMax
548               gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)          DO i=iMin,iMax
549            ENDDO           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtFacU*mT(i,j)
550            ENDDO
551         ENDDO         ENDDO
552        ENDIF        ENDIF
553    
# Line 590  C-    endif momAdvection. Line 634  C-    endif momAdvection.
634        IF (momViscosity) THEN        IF (momViscosity) THEN
635  C---  Calculate eddy fluxes (dissipation) between cells for meridional flow.  C---  Calculate eddy fluxes (dissipation) between cells for meridional flow.
636  C     Bi-harmonic term del^2 V -> v4F  C     Bi-harmonic term del^2 V -> v4F
637          IF (biharmonic)          IF (biharmonic)
638       &  CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)       &  CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
639    
640  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon
# Line 634  C--   Tendency is minus divergence of th Line 678  C--   Tendency is minus divergence of th
678          ENDIF          ENDIF
679  #endif  #endif
680    
681  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
682          IF (no_slip_sides) THEN          IF (no_slip_sides) THEN
683  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
684           CALL MOM_V_SIDEDRAG(           CALL MOM_V_SIDEDRAG(
# Line 682  c    I     myTime,myThid) Line 726  c    I     myTime,myThid)
726    
727  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
728        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
729  C      o Spherical polar grid metric terms  C      o Non-Hydrostatic (spherical) metric terms
730         CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)         CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
731         DO j=jMin,jMax         DO j=jMin,jMax
732          DO i=iMin,iMax          DO i=iMin,iMax
733           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtNHFacV*mT(i,j)
734          ENDDO          ENDDO
735         ENDDO         ENDDO
736        ENDIF        ENDIF
737        IF (usingSphericalPolarMTerms) THEN        IF ( usingSphericalPolarGrid .AND. metricTerms ) THEN
738    C      o Spherical polar grid metric terms
739         CALL MOM_V_METRIC_SPHERE(bi,bj,k,uFld,mT,myThid)         CALL MOM_V_METRIC_SPHERE(bi,bj,k,uFld,mT,myThid)
740         DO j=jMin,jMax         DO j=jMin,jMax
741          DO i=iMin,iMax          DO i=iMin,iMax
742           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtFacV*mT(i,j)
743          ENDDO          ENDDO
744         ENDDO         ENDDO
745        ENDIF        ENDIF
746        IF (usingCylindricalGrid) THEN        IF ( usingCylindricalGrid .AND. metricTerms ) THEN
747           CALL MOM_V_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)  C      o Cylindrical grid metric terms
748           DO j=jMin,jMax         CALL MOM_V_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
749              DO i=iMin,iMax         DO j=jMin,jMax
750                 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)          DO i=iMin,iMax
751              ENDDO           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtFacV*mT(i,j)
752           ENDDO          ENDDO
753           ENDDO
754        ENDIF        ENDIF
755    
756  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 737  c     ELSE Line 783  c     ELSE
783  #endif  #endif
784        ENDIF        ENDIF
785    
786        IF (nonHydrostatic.OR.quasiHydrostatic) THEN  C--   3.D Coriolis term (horizontal momentum, Eastward component: -f'*w)
787         CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)        IF ( use3dCoriolis ) THEN
788         DO j=jMin,jMax          CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
789          DO i=iMin,iMax          DO j=jMin,jMax
790           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)           DO i=iMin,iMax
791              gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
792             ENDDO
793          ENDDO          ENDDO
794         ENDDO         IF ( usingCurvilinearGrid ) THEN
795    C-     presently, non zero angleSinC array only supported with Curvilinear-Grid
796            CALL MOM_V_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
797            DO j=jMin,jMax
798             DO i=iMin,iMax
799              gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
800             ENDDO
801            ENDDO
802           ENDIF
803        ENDIF        ENDIF
804    
805  C--   Set du/dt & dv/dt on boundaries to zero  C--   Set du/dt & dv/dt on boundaries to zero

Legend:
Removed from v.1.32  
changed lines
  Added in v.1.37

  ViewVC Help
Powered by ViewVC 1.1.22