MODULE trdmod !!====================================================================== !! *** MODULE trdmod *** !! Ocean diagnostics: ocean tracers and dynamic trends !!===================================================================== !! History : 9.0 ! 04-08 (C. Talandier) Original code !! ! 05-04 (C. Deltel) Add Asselin trend in the ML budget !!---------------------------------------------------------------------- #if defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa !!---------------------------------------------------------------------- !! trd_mod : Call the trend to be computed !! trd_mod_init : Initialization step !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers variables USE dom_oce ! ocean space and time domain variables USE zdf_oce ! ocean vertical physics variables USE trdmod_oce ! ocean variables trends USE ldftra_oce ! ocean active tracers lateral physics USE sbc_oce ! surface boundary condition: ocean USE phycst ! physical constants USE trdvor ! ocean vorticity trends USE trdicp ! ocean bassin integral constraints properties USE trdmld ! ocean active mixed layer tracers trends USE in_out_manager ! I/O manager IMPLICIT NONE PRIVATE REAL(wp) :: r2dt ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 PUBLIC trd_mod ! called by all dynXX or traXX modules PUBLIC trd_mod_init ! called by opa.F90 module !! * Substitutions # include "domzgr_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt, cnbpas ) !!--------------------------------------------------------------------- !! *** ROUTINE trd_mod *** !! !! ** Purpose : Dispatch all trends computation, e.g. vorticity, mld or !! integral constraints !!---------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! time step INTEGER, INTENT( in ) :: ktrd ! tracer trend index CHARACTER(len=3), INTENT( in ) :: ctype ! momentum or tracers trends type 'DYN'/'TRA' CHARACTER(len=3), INTENT( in ), OPTIONAL :: cnbpas ! number of passage REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) :: ptrdx ! Temperature or U trend REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) :: ptrdy ! Salinity or V trend !! INTEGER :: ji, ikbu, ikbum1 INTEGER :: jj, ikbv, ikbvm1 CHARACTER(len=3) :: ccpas ! number of passage REAL(wp) :: zua, zva ! scalars REAL(wp), DIMENSION(jpi,jpj) :: ztswu, ztswv ! 2D workspace REAL(wp), DIMENSION(jpi,jpj) :: ztbfu, ztbfv ! 2D workspace REAL(wp), DIMENSION(jpi,jpj) :: z2dx, z2dy ! workspace arrays !!---------------------------------------------------------------------- z2dx(:,:) = 0.e0 ; z2dy(:,:) = 0.e0 ! initialization of workspace arrays ! Control of optional arguments ccpas = 'fst' IF( PRESENT(cnbpas) ) ccpas = cnbpas IF( neuler == 0 .AND. kt == nit000 ) THEN ; r2dt = rdt ! = rdtra (restarting with Euler time stepping) ELSEIF( kt <= nit000 + 1) THEN ; r2dt = 2. * rdt ! = 2 rdttra (leapfrog) ENDIF !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> ! I. Integral Constraints Properties for momentum and/or tracers trends !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( ( mod(kt,ntrd) == 0 .OR. kt == nit000 .OR. kt == nitend) ) THEN ! IF( lk_trdtra .AND. ctype == 'TRA' ) THEN ! active tracer trends SELECT CASE ( ktrd ) CASE ( jptra_trd_ldf ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_ldf, ctype ) ! lateral diff CASE ( jptra_trd_zdf ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_zdf, ctype ) ! vertical diff (Kz) CASE ( jptra_trd_bbc ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_bbc, ctype ) ! bottom boundary cond CASE ( jptra_trd_bbl ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_bbl, ctype ) ! bottom boundary layer CASE ( jptra_trd_npc ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_npc, ctype ) ! static instability mixing CASE ( jptra_trd_dmp ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_dmp, ctype ) ! damping CASE ( jptra_trd_qsr ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_qsr, ctype ) ! penetrative solar radiat. CASE ( jptra_trd_nsr ) z2dx(:,:) = ptrdx(:,:,1) ; z2dy(:,:) = ptrdy(:,:,1) CALL trd_icp( z2dx, z2dy, jpicpt_nsr, ctype ) ! non solar radiation CASE ( jptra_trd_xad ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_xad, ctype ) ! x- horiz adv CASE ( jptra_trd_yad ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_yad, ctype ) ! y- horiz adv CASE ( jptra_trd_zad ) ! z- vertical adv CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype, clpas=ccpas ) ! compute the surface flux condition wn(:,:,1)*tn(:,:,1) z2dx(:,:) = wn(:,:,1)*tn(:,:,1)/fse3t(:,:,1) z2dy(:,:) = wn(:,:,1)*sn(:,:,1)/fse3t(:,:,1) CALL trd_icp( z2dx , z2dy , jpicpt_zl1, ctype ) ! 1st z- vertical adv END SELECT END IF IF( lk_trddyn .AND. ctype == 'DYN' ) THEN ! momentum trends ! SELECT CASE ( ktrd ) CASE ( jpdyn_trd_hpg ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_hpg, ctype ) ! hydrost. pressure grad CASE ( jpdyn_trd_keg ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_keg, ctype ) ! KE gradient CASE ( jpdyn_trd_rvo ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_rvo, ctype ) ! relative vorticity CASE ( jpdyn_trd_pvo ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_pvo, ctype ) ! planetary vorticity CASE ( jpdyn_trd_ldf ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_ldf, ctype ) ! lateral diffusion CASE ( jpdyn_trd_zad ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_zad, ctype ) ! vertical advection CASE ( jpdyn_trd_spg ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_spg, ctype ) ! surface pressure grad. CASE ( jpdyn_trd_dat ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_dat, ctype ) ! damping term CASE ( jpdyn_trd_zdf ) ! vertical diffusion ! subtract surface forcing/bottom friction trends ! from vertical diffusive momentum trends ztswu(:,:) = 0.e0 ; ztswv(:,:) = 0.e0 ztbfu(:,:) = 0.e0 ; ztbfv(:,:) = 0.e0 DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. ! save the surface forcing momentum fluxes ztswu(ji,jj) = utau(ji,jj) / ( fse3u(ji,jj,1)*rau0 ) ztswv(ji,jj) = vtau(ji,jj) / ( fse3v(ji,jj,1)*rau0 ) ! save bottom friction momentum fluxes ikbu = MIN( mbathy(ji+1,jj ), mbathy(ji,jj) ) ikbv = MIN( mbathy(ji ,jj+1), mbathy(ji,jj) ) ikbum1 = MAX( ikbu-1, 1 ) ikbvm1 = MAX( ikbv-1, 1 ) zua = ua(ji,jj,ikbum1) * r2dt + ub(ji,jj,ikbum1) zva = va(ji,jj,ikbvm1) * r2dt + vb(ji,jj,ikbvm1) ztbfu(ji,jj) = - avmu(ji,jj,ikbu) * zua / ( fse3u(ji,jj,ikbum1)*fse3uw(ji,jj,ikbu) ) ztbfv(ji,jj) = - avmv(ji,jj,ikbv) * zva / ( fse3v(ji,jj,ikbvm1)*fse3vw(ji,jj,ikbv) ) ! ptrdx(ji,jj,1 ) = ptrdx(ji,jj,1 ) - ztswu(ji,jj) ptrdy(ji,jj,1 ) = ptrdy(ji,jj,1 ) - ztswv(ji,jj) ptrdx(ji,jj,ikbum1) = ptrdx(ji,jj,ikbum1) - ztbfu(ji,jj) ptrdy(ji,jj,ikbvm1) = ptrdy(ji,jj,ikbvm1) - ztbfv(ji,jj) END DO END DO ! CALL trd_icp( ptrdx, ptrdy, jpicpd_zdf, ctype ) CALL trd_icp( ztswu, ztswv, jpicpd_swf, ctype ) ! wind stress forcing term CALL trd_icp( ztbfu, ztbfv, jpicpd_bfr, ctype ) ! bottom friction term END SELECT ! END IF ! END IF !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> ! II. Vorticity trends !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( lk_trdvor .AND. ctype == 'DYN' ) THEN ! SELECT CASE ( ktrd ) CASE ( jpdyn_trd_hpg ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_prg ) ! Hydrostatique Pressure Gradient CASE ( jpdyn_trd_keg ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_keg ) ! KE Gradient CASE ( jpdyn_trd_rvo ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_rvo ) ! Relative Vorticity CASE ( jpdyn_trd_pvo ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_pvo ) ! Planetary Vorticity Term CASE ( jpdyn_trd_ldf ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_ldf ) ! Horizontal Diffusion CASE ( jpdyn_trd_zad ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zad ) ! Vertical Advection CASE ( jpdyn_trd_spg ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_spg ) ! Surface Pressure Grad. CASE ( jpdyn_trd_dat ) ; CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bev ) ! Beta V CASE ( jpdyn_trd_zdf ) ! Vertical Diffusion ! subtract surface forcing/bottom friction trends ! from vertical diffusive momentum trends ztswu(:,:) = 0.e0 ; ztswv(:,:) = 0.e0 ztbfu(:,:) = 0.e0 ; ztbfv(:,:) = 0.e0 DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. ! save the surface forcing momentum fluxes ztswu(ji,jj) = utau(ji,jj) / ( fse3u(ji,jj,1)*rau0 ) ztswv(ji,jj) = vtau(ji,jj) / ( fse3v(ji,jj,1)*rau0 ) ! save bottom friction momentum fluxes ikbu = MIN( mbathy(ji+1,jj ), mbathy(ji,jj) ) ikbv = MIN( mbathy(ji ,jj+1), mbathy(ji,jj) ) ikbum1 = MAX( ikbu-1, 1 ) ikbvm1 = MAX( ikbv-1, 1 ) zua = ua(ji,jj,ikbum1) * r2dt + ub(ji,jj,ikbum1) zva = va(ji,jj,ikbvm1) * r2dt + vb(ji,jj,ikbvm1) ztbfu(ji,jj) = - avmu(ji,jj,ikbu) * zua / ( fse3u(ji,jj,ikbum1)*fse3uw(ji,jj,ikbu) ) ztbfv(ji,jj) = - avmv(ji,jj,ikbv) * zva / ( fse3v(ji,jj,ikbvm1)*fse3vw(ji,jj,ikbv) ) ! ptrdx(ji,jj,1 ) = ptrdx(ji,jj,1 ) - ztswu(ji,jj) ptrdx(ji,jj,ikbum1) = ptrdx(ji,jj,ikbum1) - ztbfu(ji,jj) ptrdy(ji,jj,1 ) = ptrdy(ji,jj,1 ) - ztswv(ji,jj) ptrdy(ji,jj,ikbvm1) = ptrdy(ji,jj,ikbvm1) - ztbfv(ji,jj) END DO END DO ! CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zdf ) CALL trd_vor_zint( ztswu, ztswv, jpvor_swf ) ! Wind stress forcing term CALL trd_vor_zint( ztbfu, ztbfv, jpvor_bfr ) ! Bottom friction term END SELECT ! ENDIF !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> ! III. Mixed layer trends for active tracers !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( lk_trdmld .AND. ctype == 'TRA' ) THEN !----------------------------------------------------------------------------------------------- ! W.A.R.N.I.N.G : ! jptra_trd_ldf : called by traldf.F90 ! at this stage we store: ! - the lateral geopotential diffusion (here, lateral = horizontal) ! - and the iso-neutral diffusion if activated ! jptra_trd_zdf : called by trazdf.F90 ! * in case of iso-neutral diffusion we store the vertical diffusion component in the ! lateral trend including the K_z contrib, which will be removed later (see trd_mld) !----------------------------------------------------------------------------------------------- SELECT CASE ( ktrd ) CASE ( jptra_trd_xad ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_xad, '3D' ) ! merid. advection CASE ( jptra_trd_yad ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_yad, '3D' ) ! zonal advection CASE ( jptra_trd_zad ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zad, '3D' ) ! vertical advection CASE ( jptra_trd_ldf ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' ) ! lateral diffusive CASE ( jptra_trd_bbl ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbl, '3D' ) ! bottom boundary layer CASE ( jptra_trd_zdf ) IF( ln_traldf_iso ) THEN CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' ) ! vertical diffusion (K_z) ELSE CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zdf, '3D' ) ! vertical diffusion (K_z) ENDIF CASE ( jptra_trd_dmp ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_dmp, '3D' ) ! internal 3D restoring (tradmp) CASE ( jptra_trd_qsr ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '3D' ) ! air-sea : penetrative sol radiat CASE ( jptra_trd_nsr ) ptrdx(:,:,2:jpk) = 0.e0 ; ptrdy(:,:,2:jpk) = 0.e0 CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '2D' ) ! air-sea : non penetr sol radiat CASE ( jptra_trd_bbc ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbc, '3D' ) ! bottom bound cond (geoth flux) CASE ( jptra_trd_atf ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_atf, '3D' ) ! asselin numerical CASE ( jptra_trd_npc ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_npc, '3D' ) ! non penetr convect adjustment END SELECT ENDIF END SUBROUTINE trd_mod # else !!---------------------------------------------------------------------- !! Default case : Empty module !!---------------------------------------------------------------------- USE trdmod_oce ! ocean variables trends USE trdvor ! ocean vorticity trends USE trdicp ! ocean bassin integral constraints properties USE trdmld ! ocean active mixed layer tracers trends CONTAINS SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt, cnbpas) ! Empty routine REAL, DIMENSION(:,:,:), INTENT( in ) :: & ptrd3dx, & ! Temperature or U trend ptrd3dy ! Salinity or V trend INTEGER, INTENT( in ) :: ktrd ! momentum or tracer trend index INTEGER, INTENT( in ) :: kt ! Time step CHARACTER(len=3), INTENT( in ) :: ctype ! momentum or tracers trends type CHARACTER(len=3), INTENT( in ), OPTIONAL :: cnbpas ! number of passage WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1) WRITE(*,*) ' " ": You should not have seen this print! error ?', ptrd3dy(1,1,1) WRITE(*,*) ' " ": You should not have seen this print! error ?', ktrd WRITE(*,*) ' " ": You should not have seen this print! error ?', ctype WRITE(*,*) ' " ": You should not have seen this print! error ?', kt WRITE(*,*) ' " ": You should not have seen this print! error ?', cnbpas END SUBROUTINE trd_mod # endif SUBROUTINE trd_mod_init !!---------------------------------------------------------------------- !! *** ROUTINE trd_mod_init *** !! !! ** Purpose : Initialization of activated trends !!---------------------------------------------------------------------- USE in_out_manager ! I/O manager NAMELIST/namtrd/ ntrd, nctls, ln_trdmld_restart, ucf, ln_trdmld_instant !!---------------------------------------------------------------------- IF( l_trdtra .OR. l_trddyn ) THEN REWIND( numnam ) READ ( numnam, namtrd ) ! namelist namtrd : trends diagnostic IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) ' trd_mod_init : Momentum/Tracers trends' WRITE(numout,*) ' ~~~~~~~~~~~~~' WRITE(numout,*) ' Namelist namtrd : set trends parameters' WRITE(numout,*) ' * frequency of trends diagnostics ntrd = ', ntrd WRITE(numout,*) ' * control surface type nctls = ', nctls WRITE(numout,*) ' * restart for ML diagnostics ln_trdmld_restart = ', ln_trdmld_restart WRITE(numout,*) ' * instantaneous or mean ML T/S ln_trdmld_instant = ', ln_trdmld_instant WRITE(numout,*) ' * unit conversion factor ucf = ', ucf ENDIF ENDIF ! IF( lk_trddyn .OR. lk_trdtra ) CALL trd_icp_init ! integral constraints trends IF( lk_trdmld ) CALL trd_mld_init ! mixed-layer trends (active tracers) IF( lk_trdvor ) CALL trd_vor_init ! vorticity trends ! END SUBROUTINE trd_mod_init !!====================================================================== END MODULE trdmod