/[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.9 by jmc, Sat Feb 8 02:13:02 2003 UTC revision 1.13 by edhill, Thu Oct 9 04:19:20 2003 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,dPhihydX,dPhiHydY,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
 C  phi_hyd              :: hydrostatic pressure (perturbation)  
61  C  dPhiHydX,Y           :: Gradient (X & Y dir.) of Hydrostatic Potential  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
# Line 69  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
       _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
71        _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RL dPhiHydY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _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)
# Line 295  C---  Calculate vertical transports (at Line 293  C---  Calculate vertical transports (at
293  C---- Zonal momentum equation starts here  C---- Zonal momentum equation starts here
294    
295  C     Bi-harmonic term del^2 U -> v4F  C     Bi-harmonic term del^2 U -> v4F
296        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
297       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
298    
299  C---  Calculate mean and eddy fluxes between cells for zonal flow.  C---  Calculate mean and eddy fluxes between cells for zonal flow.
# Line 328  C     Laplacian and bi-harmonic term Line 326  C     Laplacian and bi-harmonic term
326       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)
327    
328  C     Combine fluxes -> fMer  C     Combine fluxes -> fMer
329        DO j=jMin,jMax        DO j=jMin,jMax+1
330         DO i=iMin,iMax         DO i=iMin,iMax
331          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)
332         ENDDO         ENDDO
# Line 411  C-    No-slip BCs impose a drag at botto Line 409  C-    No-slip BCs impose a drag at botto
409         ENDDO         ENDDO
410        ENDIF        ENDIF
411    
412  C--   Forcing term  C--   Forcing term (moved to timestep.F)
413        IF (momForcing)  c     IF (momForcing)
414       &  CALL EXTERNAL_FORCING_U(  c    &  CALL EXTERNAL_FORCING_U(
415       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
416       I     myTime,myThid)  c    I     myTime,myThid)
417    
418  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
419        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
# Line 447  C--   Set du/dt on boundaries to zero Line 445  C--   Set du/dt on boundaries to zero
445  C---- Meridional momentum equation starts here  C---- Meridional momentum equation starts here
446    
447  C     Bi-harmonic term del^2 V -> v4F  C     Bi-harmonic term del^2 V -> v4F
448        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
449       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
450    
451  C---  Calculate mean and eddy fluxes between cells for meridional flow.  C---  Calculate mean and eddy fluxes between cells for meridional flow.
# Line 464  C     Laplacian and bi-harmonic terms -> Line 462  C     Laplacian and bi-harmonic terms ->
462    
463  C     Combine fluxes -> fZon  C     Combine fluxes -> fZon
464        DO j=jMin,jMax        DO j=jMin,jMax
465         DO i=iMin,iMax         DO i=iMin,iMax+1
466          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)
467         ENDDO         ENDDO
468        ENDDO        ENDDO
# Line 563  C-    No-slip BCs impose a drag at botto Line 561  C-    No-slip BCs impose a drag at botto
561         ENDDO         ENDDO
562        ENDIF        ENDIF
563    
564  C--   Forcing term  C--   Forcing term (moved to timestep.F)
565        IF (momForcing)  c     IF (momForcing)
566       & CALL EXTERNAL_FORCING_V(  c    & CALL EXTERNAL_FORCING_V(
567       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
568       I     myTime,myThid)  c    I     myTime,myThid)
569    
570  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
571        IF (useNHMTerms) THEN        IF (useNHMTerms) THEN
# Line 597  C--   Set dv/dt on boundaries to zero Line 595  C--   Set dv/dt on boundaries to zero
595    
596  C--   Coriolis term  C--   Coriolis term
597  C     Note. As coded here, coriolis will not work with "thin walls"  C     Note. As coded here, coriolis will not work with "thin walls"
598  #ifdef INCLUDE_CD_CODE  c     IF (useCDscheme) THEN
599        CALL MOM_CDSCHEME(bi,bj,k,phi_hyd,dPhiHydX,dPhiHydY,myThid)  c       CALL MOM_CDSCHEME(bi,bj,k,dPhiHydX,dPhiHydY,myThid)
600  #else  c     ELSE
601        CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)        IF (.NOT.useCDscheme) THEN
602        DO j=jMin,jMax          CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)
603         DO i=iMin,iMax          DO j=jMin,jMax
604          gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)           DO i=iMin,iMax
605         ENDDO            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
606        ENDDO           ENDDO
607        CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)          ENDDO
608        DO j=jMin,jMax          CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)
609         DO i=iMin,iMax          DO j=jMin,jMax
610          gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)           DO i=iMin,iMax
611         ENDDO            gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
612        ENDDO           ENDDO
613  #endif /* INCLUDE_CD_CODE */          ENDDO
614          ENDIF
615    
616        IF (nonHydrostatic.OR.quasiHydrostatic) THEN        IF (nonHydrostatic.OR.quasiHydrostatic) THEN
617         CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)         CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
618         DO j=jMin,jMax         DO j=jMin,jMax

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22