--- MITgcm/pkg/mom_vecinv/mom_vecinv.F 2004/05/26 14:50:10 1.19 +++ MITgcm/pkg/mom_vecinv/mom_vecinv.F 2004/11/10 03:05:04 1.31 @@ -1,13 +1,13 @@ -C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/mom_vecinv/mom_vecinv.F,v 1.19 2004/05/26 14:50:10 adcroft Exp $ +C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/mom_vecinv/mom_vecinv.F,v 1.31 2004/11/10 03:05:04 jmc Exp $ C $Name: $ -#include "PACKAGES_CONFIG.h" -#include "CPP_OPTIONS.h" +#include "MOM_VECINV_OPTIONS.h" SUBROUTINE MOM_VECINV( I bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown, I dPhiHydX,dPhiHydY,KappaRU,KappaRV, U fVerU, fVerV, + O guDiss, gvDiss, I myTime, myIter, myThid) C /==========================================================\ C | S/R MOM_VECINV | @@ -31,16 +31,20 @@ #include "DYNVARS.h" #include "EEPARAMS.h" #include "PARAMS.h" +#ifdef ALLOW_MNC +#include "MNC_PARAMS.h" +#endif #include "GRID.h" #ifdef ALLOW_TIMEAVE #include "TIMEAVE_STATV.h" #endif C == Routine arguments == -C fVerU - Flux of momentum in the vertical -C fVerV direction out of the upper face of a cell K -C ( flux into the cell above ). +C fVerU :: Flux of momentum in the vertical direction, out of the upper +C fVerV :: face of a cell K ( flux into the cell above ). C dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential +C guDiss :: dissipation tendency (all explicit terms), u component +C gvDiss :: dissipation tendency (all explicit terms), v component C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation C results will be set. C kUp, kDown - Index for upper and lower layers. @@ -51,6 +55,8 @@ _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2) _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2) + _RL guDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy) + _RL gvDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy) INTEGER kUp,kDown _RL myTime INTEGER myIter @@ -64,59 +70,30 @@ EXTERNAL DIFFERENT_MULTIPLE C == Local variables == - _RL aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL uCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL vCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RL mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RL pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy) +c _RL mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RL uDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy) - _RL vDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy) C I,J,K - Loop counters INTEGER i,j,k -C rVelMaskOverride - Factor for imposing special surface boundary conditions -C ( set according to free-surface condition ). -C hFacROpen - Lopped cell factos used tohold fraction of open -C hFacRClosed and closed cell wall. - _RL rVelMaskOverride C xxxFac - On-off tracer parameters used for switching terms off. - _RL uDudxFac - _RL AhDudxFac - _RL A4DuxxdxFac - _RL vDudyFac - _RL AhDudyFac - _RL A4DuyydyFac - _RL rVelDudrFac _RL ArDudrFac - _RL fuFac _RL phxFac - _RL mtFacU - _RL uDvdxFac - _RL AhDvdxFac - _RL A4DvxxdxFac - _RL vDvdyFac - _RL AhDvdyFac - _RL A4DvyydyFac - _RL rVelDvdrFac +c _RL mtFacU _RL ArDvdrFac - _RL fvFac _RL phyFac - _RL vForcFac - _RL mtFacV - _RL wVelBottomOverride +c _RL mtFacV LOGICAL bottomDragTerms LOGICAL writeDiag _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy) @@ -124,6 +101,10 @@ _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy) _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy) +#ifdef ALLOW_MNC + INTEGER offsets(9) +#endif + #ifdef ALLOW_AUTODIFF_TAMC C-- only the kDown part of fverU/V is set in this subroutine C-- the kUp is still required @@ -133,32 +114,41 @@ fVerV(1,1,kUp) = fVerV(1,1,kUp) #endif - rVelMaskOverride=1. - IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac - wVelBottomOverride=1. - IF (k.EQ.Nr) wVelBottomOverride=0. writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime, & myTime-deltaTClock) +#ifdef ALLOW_MNC + IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN + IF ((bi .EQ. 1).AND.(bj .EQ. 1).AND.(k .EQ. 1)) THEN + CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid) + CALL MNC_CW_I_W_S('I','mom_vi',0,0,'iter',myIter,myThid) + CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid) + ENDIF + DO i = 1,9 + offsets(i) = 0 + ENDDO + offsets(3) = k +C write(*,*) 'offsets = ',(offsets(i),i=1,9) + ENDIF +#endif /* ALLOW_MNC */ + C Initialise intermediate terms DO J=1-OLy,sNy+OLy DO I=1-OLx,sNx+OLx - aF(i,j) = 0. - vF(i,j) = 0. - vrF(i,j) = 0. + vF(i,j) = 0. + vrF(i,j) = 0. uCf(i,j) = 0. vCf(i,j) = 0. - mT(i,j) = 0. - pF(i,j) = 0. +c mT(i,j) = 0. del2u(i,j) = 0. del2v(i,j) = 0. dStar(i,j) = 0. zStar(i,j) = 0. - uDiss(i,j) = 0. - vDiss(i,j) = 0. + guDiss(i,j)= 0. + gvDiss(i,j)= 0. vort3(i,j) = 0. - omega3(i,j) = 0. - ke(i,j) = 0. + omega3(i,j)= 0. + ke(i,j) = 0. #ifdef ALLOW_AUTODIFF_TAMC strain(i,j) = 0. _d 0 tension(i,j) = 0. _d 0 @@ -168,30 +158,13 @@ C-- Term by term tracer parmeters C o U momentum equation - uDudxFac = afFacMom*1. - AhDudxFac = vfFacMom*1. - A4DuxxdxFac = vfFacMom*1. - vDudyFac = afFacMom*1. - AhDudyFac = vfFacMom*1. - A4DuyydyFac = vfFacMom*1. - rVelDudrFac = afFacMom*1. ArDudrFac = vfFacMom*1. - mTFacU = mtFacMom*1. - fuFac = cfFacMom*1. +c mTFacU = mtFacMom*1. phxFac = pfFacMom*1. C o V momentum equation - uDvdxFac = afFacMom*1. - AhDvdxFac = vfFacMom*1. - A4DvxxdxFac = vfFacMom*1. - vDvdyFac = afFacMom*1. - AhDvdyFac = vfFacMom*1. - A4DvyydyFac = vfFacMom*1. - rVelDvdrFac = afFacMom*1. ArDvdrFac = vfFacMom*1. - mTFacV = mtFacMom*1. - fvFac = cfFacMom*1. +c mTFacV = mtFacMom*1. phyFac = pfFacMom*1. - vForcFac = foFacMom*1. IF ( no_slip_bottom & .OR. bottomDragQuadratic.NE.0. @@ -210,17 +183,6 @@ C-- Calculate open water fraction at vorticity points CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid) -C---- Calculate common quantities used in both U and V equations -C Calculate tracer cell face open areas - DO j=1-OLy,sNy+OLy - DO i=1-OLx,sNx+OLx - xA(i,j) = _dyG(i,j,bi,bj) - & *drF(k)*_hFacW(i,j,k,bi,bj) - yA(i,j) = _dxG(i,j,bi,bj) - & *drF(k)*_hFacS(i,j,k,bi,bj) - ENDDO - ENDDO - C Make local copies of horizontal flow field DO j=1-OLy,sNy+OLy DO i=1-OLx,sNx+OLx @@ -239,11 +201,13 @@ CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid) -c CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid) + IF (useAbsVorticity) + & CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid) IF (momViscosity) THEN C Calculate del^2 u and del^2 v for bi-harmonic term - IF (viscA4.NE.0. + IF ( (viscA4.NE.0. .AND. no_slip_sides) + & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. & .OR. viscA4Grid.NE.0. & .OR. viscC4leith.NE.0. & ) THEN @@ -256,12 +220,13 @@ ENDIF C Calculate dissipation terms for U and V equations C in terms of vorticity and divergence - IF (viscAh.NE.0. .OR. viscA4.NE.0. - & .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0. - & .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0. + IF ( viscAhD.NE.0. .OR. viscAhZ.NE.0. + & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. + & .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0. + & .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0. & ) THEN CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar, - O uDiss,vDiss, + O guDiss,gvDiss, & myThid) ENDIF C or in terms of tension and strain @@ -274,7 +239,7 @@ I myThid) CALL MOM_HDISSIP(bi,bj,k, I tension,strain,hFacZ,viscAtension,viscAstrain, - O uDiss,vDiss, + O guDiss,gvDiss, I myThid) ENDIF ENDIF @@ -287,28 +252,28 @@ C-- Vertical flux (fVer is at upper face of "u" cell) C Eddy component of vertical flux (interior component only) -> vrF - IF (momViscosity.AND..NOT.implicitViscosity) - & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid) + IF (momViscosity.AND..NOT.implicitViscosity) THEN + CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid) C Combine fluxes - DO j=jMin,jMax - DO i=iMin,iMax - fVerU(i,j,kDown) = ArDudrFac*vrF(i,j) + DO j=jMin,jMax + DO i=iMin,iMax + fVerU(i,j,kDown) = ArDudrFac*vrF(i,j) + ENDDO ENDDO - ENDDO -C-- Tendency is minus divergence of the fluxes + coriolis + pressure term - DO j=2-Oly,sNy+Oly-1 - DO i=2-Olx,sNx+Olx-1 - gU(i,j,k,bi,bj) = uDiss(i,j) +C-- Tendency is minus divergence of the fluxes + DO j=2-Oly,sNy+Oly-1 + DO i=2-Olx,sNx+Olx-1 + guDiss(i,j) = guDiss(i,j) & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k) & *recip_rAw(i,j,bi,bj) & *( & +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac & ) - & - phxFac*dPhiHydX(i,j) + ENDDO ENDDO - ENDDO + ENDIF C-- No-slip and drag BCs appear as body forces in cell abutting topography IF (momViscosity.AND.no_slip_sides) THEN @@ -316,7 +281,7 @@ CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid) DO j=jMin,jMax DO i=iMin,iMax - gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j) + guDiss(i,j) = guDiss(i,j)+vF(i,j) ENDDO ENDDO ENDIF @@ -326,7 +291,7 @@ CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid) DO j=jMin,jMax DO i=iMin,iMax - gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j) + guDiss(i,j) = guDiss(i,j)+vF(i,j) ENDDO ENDDO ENDIF @@ -347,28 +312,28 @@ C-- Vertical flux (fVer is at upper face of "v" cell) C Eddy component of vertical flux (interior component only) -> vrF - IF (momViscosity.AND..NOT.implicitViscosity) - & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid) + IF (momViscosity.AND..NOT.implicitViscosity) THEN + CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid) C Combine fluxes -> fVerV - DO j=jMin,jMax - DO i=iMin,iMax - fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j) + DO j=jMin,jMax + DO i=iMin,iMax + fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j) + ENDDO ENDDO - ENDDO -C-- Tendency is minus divergence of the fluxes + coriolis + pressure term - DO j=jMin,jMax - DO i=iMin,iMax - gV(i,j,k,bi,bj) = vDiss(i,j) +C-- Tendency is minus divergence of the fluxes + DO j=jMin,jMax + DO i=iMin,iMax + gvDiss(i,j) = gvDiss(i,j) & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k) & *recip_rAs(i,j,bi,bj) & *( & +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac & ) - & - phyFac*dPhiHydY(i,j) + ENDDO ENDDO - ENDDO + ENDIF C-- No-slip and drag BCs appear as body forces in cell abutting topography IF (momViscosity.AND.no_slip_sides) THEN @@ -376,7 +341,7 @@ CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid) DO j=jMin,jMax DO i=iMin,iMax - gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j) + gvDiss(i,j) = gvDiss(i,j)+vF(i,j) ENDDO ENDDO ENDIF @@ -385,7 +350,7 @@ CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid) DO j=jMin,jMax DO i=iMin,iMax - gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j) + gvDiss(i,j) = gvDiss(i,j)+vF(i,j) ENDDO ENDDO ENDIF @@ -402,35 +367,61 @@ c ENDIF C-- Horizontal Coriolis terms - IF (useCoriolis .AND. .NOT.useCDscheme) THEN - CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,omega3,hFacZ,r_hFacZ, + IF (useCoriolis .AND. .NOT.useCDscheme + & .AND. .NOT. useAbsVorticity) THEN + CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ, & uCf,vCf,myThid) DO j=jMin,jMax DO i=iMin,iMax - gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j) - gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j) + gU(i,j,k,bi,bj) = uCf(i,j) - phxFac*dPhiHydX(i,j) + gV(i,j,k,bi,bj) = vCf(i,j) - phyFac*dPhiHydY(i,j) ENDDO ENDDO IF ( writeDiag ) THEN - CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid) + IF (snapshot_mdsio) THEN + CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid) + ENDIF +#ifdef ALLOW_MNC + IF (useMNC .AND. snapshot_mnc) THEN + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fV', uCf, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fU', vCf, + & offsets, myThid) + ENDIF +#endif /* ALLOW_MNC */ ENDIF + ELSE + DO j=jMin,jMax + DO i=iMin,iMax + gU(i,j,k,bi,bj) = -phxFac*dPhiHydX(i,j) + gV(i,j,k,bi,bj) = -phyFac*dPhiHydY(i,j) + ENDDO + ENDDO ENDIF IF (momAdvection) THEN C-- Horizontal advection of relative vorticity -c CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,r_hFacZ,uCf,myThid) - CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3,hFacZ,r_hFacZ, - & uCf,myThid) + IF (useAbsVorticity) THEN + CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ, + & uCf,myThid) + ELSE + CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3,hFacZ,r_hFacZ, + & uCf,myThid) + ENDIF c CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid) DO j=jMin,jMax DO i=iMin,iMax gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j) ENDDO ENDDO -c CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,r_hFacZ,vCf,myThid) - CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3,hFacZ,r_hFacZ, - & vCf,myThid) + IF (useAbsVorticity) THEN + CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ, + & vCf,myThid) + ELSE + CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3,hFacZ,r_hFacZ, + & vCf,myThid) + ENDIF c CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid) DO j=jMin,jMax DO i=iMin,iMax @@ -439,9 +430,20 @@ ENDDO IF ( writeDiag ) THEN - CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('zU','I10',1,vCf,bi,bj,k,myIter,myThid) + IF (snapshot_mdsio) THEN + CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('zU','I10',1,vCf,bi,bj,k,myIter,myThid) + ENDIF +#ifdef ALLOW_MNC + IF (useMNC .AND. snapshot_mnc) THEN + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zV', uCf, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zU', vCf, + & offsets, myThid) + ENDIF +#endif /* ALLOW_MNC */ ENDIF + #ifdef ALLOW_TIMEAVE #ifndef HRCUBE IF (taveFreq.GT.0.) THEN @@ -450,8 +452,8 @@ CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock, & Nr, k, bi, bj, myThid) ENDIF -#endif /* ALLOW_TIMEAVE */ #endif /* ndef HRCUBE */ +#endif /* ALLOW_TIMEAVE */ C-- Vertical shear terms (-w*du/dr & -w*dv/dr) IF ( .NOT. momImplVertAdv ) THEN @@ -483,8 +485,18 @@ ENDDO ENDDO IF ( writeDiag ) THEN - CALL WRITE_LOCAL_RL('KEx','I10',1,uCf,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('KEy','I10',1,vCf,bi,bj,k,myIter,myThid) + IF (snapshot_mdsio) THEN + CALL WRITE_LOCAL_RL('KEx','I10',1,uCf,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('KEy','I10',1,vCf,bi,bj,k,myIter,myThid) + ENDIF +#ifdef ALLOW_MNC + IF (useMNC .AND. snapshot_mnc) THEN + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEx', uCf, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEy', vCf, + & offsets, myThid) + ENDIF +#endif /* ALLOW_MNC */ ENDIF C-- end if momAdvection @@ -498,18 +510,50 @@ ENDDO ENDDO +#ifdef ALLOW_DEBUG + IF ( debugLevel .GE. debLevB + & .AND. k.EQ.4 .AND. myIter.EQ.nIter0 + & .AND. nPx.EQ.1 .AND. nPy.EQ.1 + & .AND. useCubedSphereExchange ) THEN + CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV', + & guDiss,gvDiss, k, standardMessageUnit,bi,bj,myThid ) + ENDIF +#endif /* ALLOW_DEBUG */ IF ( writeDiag ) THEN - CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid) -c CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid) - CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid) + IF (snapshot_mdsio) THEN + CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter, + & myThid) + CALL WRITE_LOCAL_RL('Du','I10',1,guDiss,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('Dv','I10',1,gvDiss,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid) + CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid) + ENDIF +#ifdef ALLOW_MNC + IF (useMNC .AND. snapshot_mnc) THEN + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Ds',strain, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dt',tension, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Du',guDiss, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dv',gvDiss, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Z3',vort3, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'W3',omega3, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'KE',KE, + & offsets, myThid) + CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'D', hdiv, + & offsets, myThid) + ENDIF +#endif /* ALLOW_MNC */ ENDIF - + #endif /* ALLOW_MOM_VECINV */ RETURN