/[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.35 by heimbach, Wed May 3 23:35:11 2006 UTC revision 1.38 by jmc, Thu Nov 23 00:45:18 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  #ifdef ALLOW_AUTODIFF_TAMC
56  # include "tamc.h"  # include "tamc.h"
57  # include "tamc_keys.h"  # include "tamc_keys.h"
58  # include "MOM_FLUXFORM.h"  # include "MOM_FLUXFORM.h"
# Line 98  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  #ifdef ALLOW_AUTODIFF_TAMC
102        INTEGER imomkey        INTEGER imomkey
103  #endif  #endif
104        _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 110  C  fVrUp,fVrDw          :: vertical visc Line 110  C  fVrUp,fVrDw          :: vertical visc
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 on and off.  C     afFacMom     :: Tracer parameters for turning terms on and off.
113  C     vfFacMom          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
# Line 169  CEOP Line 169  CEOP
169            act3 = myThid - 1            act3 = myThid - 1
170            max3 = nTx*nTy            max3 = nTx*nTy
171            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
172            imomkey = (act0 + 1)            imomkey = (act0 + 1)
173       &                    + act1*max0       &                    + act1*max0
174       &                    + act2*max0*max1       &                    + act2*max0*max1
175       &                    + act3*max0*max1*max2       &                    + act3*max0*max1*max2
# Line 189  C     Initialise intermediate terms Line 189  C     Initialise intermediate terms
189          fVrDw(i,j)= 0.          fVrDw(i,j)= 0.
190          rTransU(i,j)= 0.          rTransU(i,j)= 0.
191          rTransV(i,j)= 0.          rTransV(i,j)= 0.
192    c       KE(i,j)     = 0.
193    c       hDiv(i,j)   = 0.
194            vort3(i,j)  = 0.
195          strain(i,j) = 0.          strain(i,j) = 0.
196          tension(i,j)= 0.          tension(i,j)= 0.
197          guDiss(i,j) = 0.          guDiss(i,j) = 0.
198          gvDiss(i,j) = 0.          gvDiss(i,j) = 0.
 #ifdef ALLOW_AUTODIFF_TAMC  
         vort3(i,j)   = 0. _d 0  
         strain(i,j)  = 0. _d 0  
         tension(i,j) = 0. _d 0  
 #endif  
199         ENDDO         ENDDO
200        ENDDO        ENDDO
201    
# Line 304  C---  First call (k=1): compute vertical Line 302  C---  First call (k=1): compute vertical
302  C-    Calculate vertical transports above U & V points (West & South face):  C-    Calculate vertical transports above U & V points (West & South face):
303    
304  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
305    # ifdef NONLIN_FRSURF
306    #  ifndef DISABLE_RSTAR_CODE
307  CADJ STORE dwtransc(:,:,bi,bj) =  CADJ STORE dwtransc(:,:,bi,bj) =
308  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
309  CADJ STORE dwtransu(:,:,bi,bj) =  CADJ STORE dwtransu(:,:,bi,bj) =
310  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
311  CADJ STORE dwtransv(:,:,bi,bj) =  CADJ STORE dwtransv(:,:,bi,bj) =
312  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte  CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
313    #  endif
314    # endif /* NONLIN_FRSURF */
315  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
316          CALL MOM_CALC_RTRANS( k, bi, bj,          CALL MOM_CALC_RTRANS( k, bi, bj,
317       O                        rTransU, rTransV,       O                        rTransU, rTransV,
# Line 428  C-    endif momAdvection. Line 430  C-    endif momAdvection.
430  C---  Calculate eddy fluxes (dissipation) between cells for zonal flow.  C---  Calculate eddy fluxes (dissipation) between cells for zonal flow.
431    
432  C     Bi-harmonic term del^2 U -> v4F  C     Bi-harmonic term del^2 U -> v4F
433          IF (biharmonic)          IF (biharmonic)
434       &  CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)       &  CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
435    
436  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon
# Line 472  C--   Tendency is minus divergence of th Line 474  C--   Tendency is minus divergence of th
474          ENDIF          ENDIF
475  #endif  #endif
476    
477  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
478          IF (no_slip_sides) THEN          IF (no_slip_sides) THEN
479  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
480           CALL MOM_U_SIDEDRAG(           CALL MOM_U_SIDEDRAG(
# Line 630  C-    endif momAdvection. Line 632  C-    endif momAdvection.
632        IF (momViscosity) THEN        IF (momViscosity) THEN
633  C---  Calculate eddy fluxes (dissipation) between cells for meridional flow.  C---  Calculate eddy fluxes (dissipation) between cells for meridional flow.
634  C     Bi-harmonic term del^2 V -> v4F  C     Bi-harmonic term del^2 V -> v4F
635          IF (biharmonic)          IF (biharmonic)
636       &  CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)       &  CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
637    
638  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon  C     Laplacian and bi-harmonic terms, Zonal  Fluxes -> fZon
# Line 674  C--   Tendency is minus divergence of th Line 676  C--   Tendency is minus divergence of th
676          ENDIF          ENDIF
677  #endif  #endif
678    
679  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
680          IF (no_slip_sides) THEN          IF (no_slip_sides) THEN
681  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
682           CALL MOM_V_SIDEDRAG(           CALL MOM_V_SIDEDRAG(
# Line 780  c     ELSE Line 782  c     ELSE
782        ENDIF        ENDIF
783    
784  C--   3.D Coriolis term (horizontal momentum, Eastward component: -f'*w)  C--   3.D Coriolis term (horizontal momentum, Eastward component: -f'*w)
785        IF ( nonHydrostatic.OR.quasiHydrostatic ) THEN        IF ( use3dCoriolis ) THEN
786          CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)          CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
787          DO j=jMin,jMax          DO j=jMin,jMax
788           DO i=iMin,iMax           DO i=iMin,iMax

Legend:
Removed from v.1.35  
changed lines
  Added in v.1.38

  ViewVC Help
Powered by ViewVC 1.1.22