MODULE traldf_iso !!====================================================================== !! *** MODULE traldf_iso *** !! Ocean active tracers: horizontal component of the lateral tracer mixing trend !!====================================================================== !! History : ! 94-08 (G. Madec, M. Imbard) !! ! 97-05 (G. Madec) split into traldf and trazdf !! 8.5 ! 02-08 (G. Madec) Free form, F90 !! 9.0 ! 05-11 (G. Madec) merge traldf and trazdf :-) !!---------------------------------------------------------------------- #if defined key_ldfslp || defined key_esopa !!---------------------------------------------------------------------- !! 'key_ldfslp' slope of the lateral diffusive direction !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tra_ldf_iso : update the tracer trend with the horizontal !! component of a iso-neutral laplacian operator !! and with the vertical part of !! the isopycnal or geopotential s-coord. operator !!---------------------------------------------------------------------- USE oce ! ocean dynamics and active tracers USE dom_oce ! ocean space and time domain USE ldftra_oce ! ocean active tracers: lateral physics USE trdmod ! ocean active tracers trends USE trdmod_oce ! ocean variables trends USE zdf_oce ! ocean vertical physics USE in_out_manager ! I/O manager USE ldfslp ! iso-neutral slopes USE diaptr ! poleward transport diagnostics USE prtctl ! Print control IMPLICIT NONE PRIVATE PUBLIC tra_ldf_iso ! routine called by step.F90 !! * Substitutions # include "domzgr_substitute.h90" # include "ldftra_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Header$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tra_ldf_iso( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_ldf_iso *** !! !! ** Purpose : Compute the before horizontal tracer (t & s) diffusive !! trend for a laplacian tensor (ezxcept the dz[ dz[.] ] term) and !! add it to the general trend of tracer equation. !! !! ** Method : The horizontal component of the lateral diffusive trends !! is provided by a 2nd order operator rotated along neural or geopo- !! tential surfaces to which an eddy induced advection can be added !! It is computed using before fields (forward in time) and isopyc- !! nal or geopotential slopes computed in routine ldfslp. !! !! 1st part : masked horizontal derivative of T & S ( di[ t ] ) !! ======== with partial cell update if ln_zps=T. !! !! 2nd part : horizontal fluxes of the lateral mixing operator !! ======== !! zftu = (aht+ahtb0) e2u*e3u/e1u di[ tb ] !! - aht e2u*uslp dk[ mi(mk(tb)) ] !! zftv = (aht+ahtb0) e1v*e3v/e2v dj[ tb ] !! - aht e2u*vslp dk[ mj(mk(tb)) ] !! take the horizontal divergence of the fluxes: !! difft = 1/(e1t*e2t*e3t) { di-1[ zftu ] + dj-1[ zftv ] } !! Add this trend to the general trend (ta,sa): !! ta = ta + difft !! !! 3rd part: vertical trends of the lateral mixing operator !! ======== (excluding the vertical flux proportional to dk[t] ) !! vertical fluxes associated with the rotated lateral mixing: !! zftw =-aht { e2t*wslpi di[ mi(mk(tb)) ] !! + e1t*wslpj dj[ mj(mk(tb)) ] } !! take the horizontal divergence of the fluxes: !! difft = 1/(e1t*e2t*e3t) dk[ zftw ] !! Add this trend to the general trend (ta,sa): !! ta = ta + difft !! !! ** Action : Update (ta,sa) arrays with the before rotated diffusion !! trend (except the dk[ dk[.] ] term) !!---------------------------------------------------------------------- USE oce , zftv => ua ! use ua as workspace USE oce , zfsv => va ! use va as workspace !! INTEGER, INTENT( in ) :: kt ! ocean time-step index !! INTEGER :: ji, jj, jk ! dummy loop indices INTEGER :: iku, ikv ! temporary integer REAL(wp) :: zmsku, zabe1, zcof1, zcoef3, zta ! temporary scalars REAL(wp) :: zmskv, zabe2, zcof2, zcoef4, zsa ! " " REAL(wp) :: zcoef0, zbtr ! " " REAL(wp), DIMENSION(jpi,jpj) :: zdkt , zdk1t, zftu ! 2D workspace REAL(wp), DIMENSION(jpi,jpj) :: zdks , zdk1s, zfsu ! " " REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdit, zdjt, ztfw ! 3D workspace REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdis, zdjs, zsfw ! " " !!---------------------------------------------------------------------- IF( kt == nit000 ) THEN IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator' IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' ENDIF !!---------------------------------------------------------------------- !! I - masked horizontal derivative of T & S !!---------------------------------------------------------------------- !!bug ajout.... why? ( 1,jpj,:) and (jpi,1,:) should be sufficient.... zdit (1,:,:) = 0.e0 ; zdit (jpi,:,:) = 0.e0 zdis (1,:,:) = 0.e0 ; zdis (jpi,:,:) = 0.e0 zdjt (1,:,:) = 0.e0 ; zdjt (jpi,:,:) = 0.e0 zdjs (1,:,:) = 0.e0 ; zdjs (jpi,:,:) = 0.e0 !!end ! Horizontal temperature and salinity gradient DO jk = 1, jpkm1 DO jj = 1, jpjm1 DO ji = 1, fs_jpim1 ! vector opt. zdit(ji,jj,jk) = ( tb(ji+1,jj ,jk) - tb(ji,jj,jk) ) * umask(ji,jj,jk) zdis(ji,jj,jk) = ( sb(ji+1,jj ,jk) - sb(ji,jj,jk) ) * umask(ji,jj,jk) zdjt(ji,jj,jk) = ( tb(ji ,jj+1,jk) - tb(ji,jj,jk) ) * vmask(ji,jj,jk) zdjs(ji,jj,jk) = ( sb(ji ,jj+1,jk) - sb(ji,jj,jk) ) * vmask(ji,jj,jk) END DO END DO END DO IF( ln_zps ) THEN ! partial steps correction at the last level DO jj = 1, jpjm1 DO ji = 1, fs_jpim1 ! vector opt. ! last level iku = MIN( mbathy(ji,jj), mbathy(ji+1,jj ) ) - 1 ikv = MIN( mbathy(ji,jj), mbathy(ji ,jj+1) ) - 1 zdit(ji,jj,iku) = gtu(ji,jj) zdis(ji,jj,iku) = gsu(ji,jj) zdjt(ji,jj,ikv) = gtv(ji,jj) zdjs(ji,jj,ikv) = gsv(ji,jj) END DO END DO ENDIF !!---------------------------------------------------------------------- !! II - horizontal trend of T & S (full) !!---------------------------------------------------------------------- !CDIR PARALLEL DO PRIVATE( zdk1t, zdk1s, zftu, zfsu ) ! ! =============== DO jk = 1, jpkm1 ! Horizontal slab ! ! =============== ! 1. Vertical tracer gradient at level jk and jk+1 ! ------------------------------------------------ ! surface boundary condition: zdkt(jk=1)=zdkt(jk=2) zdk1t(:,:) = ( tb(:,:,jk) - tb(:,:,jk+1) ) * tmask(:,:,jk+1) zdk1s(:,:) = ( sb(:,:,jk) - sb(:,:,jk+1) ) * tmask(:,:,jk+1) IF( jk == 1 ) THEN zdkt(:,:) = zdk1t(:,:) zdks(:,:) = zdk1s(:,:) ELSE zdkt(:,:) = ( tb(:,:,jk-1) - tb(:,:,jk) ) * tmask(:,:,jk) zdks(:,:) = ( sb(:,:,jk-1) - sb(:,:,jk) ) * tmask(:,:,jk) ENDIF ! 2. Horizontal fluxes ! -------------------- DO jj = 1 , jpjm1 DO ji = 1, fs_jpim1 ! vector opt. zabe1 = ( fsahtu(ji,jj,jk) + ahtb0 ) * e2u(ji,jj) * fse3u(ji,jj,jk) / e1u(ji,jj) zabe2 = ( fsahtv(ji,jj,jk) + ahtb0 ) * e1v(ji,jj) * fse3v(ji,jj,jk) / e2v(ji,jj) zmsku = 1. / MAX( tmask(ji+1,jj,jk ) + tmask(ji,jj,jk+1) & & + tmask(ji+1,jj,jk+1) + tmask(ji,jj,jk ), 1. ) zmskv = 1. / MAX( tmask(ji,jj+1,jk ) + tmask(ji,jj,jk+1) & & + tmask(ji,jj+1,jk+1) + tmask(ji,jj,jk ), 1. ) zcof1 = -fsahtu(ji,jj,jk) * e2u(ji,jj) * uslp(ji,jj,jk) * zmsku zcof2 = -fsahtv(ji,jj,jk) * e1v(ji,jj) * vslp(ji,jj,jk) * zmskv zftu(ji,jj ) = ( zabe1 * zdit(ji,jj,jk) & & + zcof1 * ( zdkt (ji+1,jj) + zdk1t(ji,jj) & & + zdk1t(ji+1,jj) + zdkt (ji,jj) ) ) * umask(ji,jj,jk) zftv(ji,jj,jk) = ( zabe2 * zdjt(ji,jj,jk) & & + zcof2 * ( zdkt (ji,jj+1) + zdk1t(ji,jj) & & + zdk1t(ji,jj+1) + zdkt (ji,jj) ) ) * vmask(ji,jj,jk) zfsu(ji,jj ) = ( zabe1 * zdis(ji,jj,jk) & & + zcof1 * ( zdks (ji+1,jj) + zdk1s(ji,jj) & & + zdk1s(ji+1,jj) + zdks (ji,jj) ) ) * umask(ji,jj,jk) zfsv(ji,jj,jk) = ( zabe2 * zdjs(ji,jj,jk) & & + zcof2 * ( zdks (ji,jj+1) + zdk1s(ji,jj) & & + zdk1s(ji,jj+1) + zdks (ji,jj) ) ) * vmask(ji,jj,jk) END DO END DO ! II.4 Second derivative (divergence) and add to the general trend ! ---------------------------------------------------------------- DO jj = 2 , jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. zbtr= 1. / ( e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,jk) ) zta = zbtr * ( zftu(ji,jj ) - zftu(ji-1,jj ) + zftv(ji,jj,jk) - zftv(ji,jj-1,jk) ) zsa = zbtr * ( zfsu(ji,jj ) - zfsu(ji-1,jj ) + zfsv(ji,jj,jk) - zfsv(ji,jj-1,jk) ) ta (ji,jj,jk) = ta (ji,jj,jk) + zta sa (ji,jj,jk) = sa (ji,jj,jk) + zsa END DO END DO ! ! =============== END DO ! End of slab ! ! =============== IF( ln_diaptr .AND. ( MOD( kt, nf_ptr ) == 0 ) ) THEN ! Poleward diffusive heat and salt transports pht_ldf(:) = ptr_vj( zftv(:,:,:) ) pst_ldf(:) = ptr_vj( zfsv(:,:,:) ) ENDIF !!---------------------------------------------------------------------- !! III - vertical trend of T & S (extra diagonal terms only) !!---------------------------------------------------------------------- ! Local constant initialization ! ----------------------------- ztfw(1,:,:) = 0.e0 ; ztfw(jpi,:,:) = 0.e0 zsfw(1,:,:) = 0.e0 ; zsfw(jpi,:,:) = 0.e0 ! Vertical fluxes ! --------------- ! Surface and bottom vertical fluxes set to zero ztfw(:,:, 1 ) = 0.e0 ; ztfw(:,:,jpk) = 0.e0 zsfw(:,:, 1 ) = 0.e0 ; zsfw(:,:,jpk) = 0.e0 ! interior (2=