MODULE trdmod !!====================================================================== !! *** MODULE trdmod *** !! Ocean diagnostics: ocean tracers and dynamic trends !!===================================================================== !! History : 1.0 ! 2004-08 (C. Talandier) Original code !! - ! 2005-04 (C. Deltel) Add Asselin trend in the ML budget !! 3.3 ! 2010-10 (C. Ethe, G. Madec) reorganisation of initialisation phase !! 3.5 ! 2012-02 (G. Madec) add 3D trends output for T, S, U, V, PE and KE !!---------------------------------------------------------------------- #if defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa !!---------------------------------------------------------------------- !! trd_mod : manage the type of trend diagnostics !! trd_3Diom : output 3D momentum and/or tracer trends using IOM !! trd_budget : domain averaged budget of trends (including kinetic energy and tracer variance trends) !! 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 USE iom ! I/O manager library USE lib_mpp ! MPP library USE wrk_nemo ! Memory allocation 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" !!---------------------------------------------------------------------- !! NEMO/OPA 3.3 , NEMO Consortium (2010) !! $Id$ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trd_mod *** !! !! ** Purpose : Dispatch all trends computation, e.g. 3D output, integral !! constraints, barotropic vorticity, kinetic enrgy, !! potential energy, and/or mixed layer budget. !!---------------------------------------------------------------------- REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend INTEGER , INTENT(in ) :: ktrd ! tracer trend index CHARACTER(len=3) , INTENT(in ) :: ctype ! momentum or tracers trends type 'DYN'/'TRA' INTEGER , INTENT(in ) :: kt ! time step !! INTEGER :: ji, jj ! dummy loop indices REAL(wp), POINTER, DIMENSION(:,:) :: ztswu, ztswv ! 2D workspace !!---------------------------------------------------------------------- CALL wrk_alloc( jpi, jpj, ztswu, ztswv ) IF( neuler == 0 .AND. kt == nit000 ) THEN ; r2dt = rdt ! = rdtra (restart with Euler time stepping) ELSEIF( kt <= nit000 + 1) THEN ; r2dt = 2. * rdt ! = 2 rdttra (leapfrog) ENDIF ! !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( ln_3D_trd_d .OR. ln_3D_trd_t ) THEN ! 3D output of momentum and/or tracers trends using IOM interface ! !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< CALL trd_3Diom ( ptrdx, ptrdy, ktrd, ctype, kt ) ! ENDIF ! !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( ln_glo_trd ) THEN ! I. Integral Constraints Properties for momentum and/or tracers trends ! !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< CALL trd_budget( ptrdx, ptrdy, ktrd, ctype, kt ) ! ENDIF ! !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< IF( lk_trdvor .AND. ctype == 'DYN' ) THEN ! II. Vorticity trends ! !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 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_zdf ) ! Vertical Diffusion ztswu(:,:) = 0.e0 ; ztswv(:,:) = 0.e0 DO jj = 2, jpjm1 ! wind stress trends DO ji = fs_2, fs_jpim1 ! vector opt. ztswu(ji,jj) = ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(ji,jj,1) * rau0 ) ztswv(ji,jj) = ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(ji,jj,1) * rau0 ) END DO END DO ! CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zdf ) ! zdf trend including surf./bot. stresses CALL trd_vor_zint( ztswu, ztswv, jpvor_swf ) ! surface wind stress CASE ( jpdyn_trd_bfr ) CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bfr ) ! Bottom stress 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' ) ! zonal advection CASE ( jptra_trd_yad ) ; CALL trd_mld_zint( ptrdx, ptrdy, jpmld_yad, '3D' ) ! merid. 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 diffusion 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' ) ! lateral 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._wp ; ptrdy(:,:,2:jpk) = 0._wp 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 ! CALL wrk_dealloc( jpi, jpj, ztswu, ztswv ) ! END SUBROUTINE trd_mod SUBROUTINE trd_budget( ptrdx, ptrdy, ktrd, ctype, kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trd_budget *** !! !! ** Purpose : integral constraint diagnostics for momentum and/or tracer trends !! !!---------------------------------------------------------------------- REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend INTEGER , INTENT(in ) :: ktrd ! tracer trend index CHARACTER(len=3) , INTENT(in ) :: ctype ! momentum or tracers trends type 'DYN'/'TRA' INTEGER , INTENT(in ) :: kt ! time step !! INTEGER :: ji, jj ! dummy loop indices REAL(wp), POINTER, DIMENSION(:,:) :: ztswu, ztswv, z2dx, z2dy ! 2D workspace !!---------------------------------------------------------------------- CALL wrk_alloc( jpi, jpj, ztswu, ztswv, z2dx, z2dy ) IF( MOD(kt,nn_trd) == 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) ! non solar radiation z2dy(:,:) = ptrdy(:,:,1) CALL trd_icp( z2dx , z2dy , jpicpt_nsr, ctype ) 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 ) ; CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype ) ! z- vertical adv ! ! surface flux IF( lk_vvl ) THEN ! variable volume = zero z2dx(:,:) = 0._wp z2dy(:,:) = 0._wp ELSE ! constant volume = wn*tsn/e3t z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) ENDIF CALL trd_icp( z2dx , z2dy , jpicpt_zl1, ctype ) END SELECT ENDIF 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 gradient CASE( jpdyn_trd_spg ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_spg, ctype ) ! surface pressure grad. CASE( jpdyn_trd_pvo ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_pvo, ctype ) ! planetary vorticity CASE( jpdyn_trd_rvo ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_rvo, ctype ) ! relative vorticity or metric term CASE( jpdyn_trd_keg ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_keg, ctype ) ! KE gradient or hor. advection CASE( jpdyn_trd_zad ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_zad, ctype ) ! vertical advection CASE( jpdyn_trd_ldf ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_ldf, ctype ) ! lateral diffusion CASE( jpdyn_trd_zdf ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_zdf, ctype ) ! vertical diffusion (icluding bfr & tau) ztswu(:,:) = ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(:,:,1) * rau0 ) ztswv(:,:) = ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(:,:,1) * rau0 ) CALL trd_icp( ztswu, ztswv, jpicpd_swf, ctype ) ! wind stress trends CASE( jpdyn_trd_bfr ) ; CALL trd_icp( ptrdx, ptrdy, jpicpd_bfr, ctype ) ! bottom friction trends END SELECT ! ENDIF ! ENDIF ! CALL wrk_dealloc( jpi, jpj, ztswu, ztswv, z2dx, z2dy ) ! END SUBROUTINE trd_budget SUBROUTINE trd_3Diom( ptrdx, ptrdy, ktrd, ctype, kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trd_3Diom *** !! !! ** Purpose : output 3D trends using IOM !!---------------------------------------------------------------------- REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend INTEGER , INTENT(in ) :: ktrd ! tracer trend index CHARACTER(len=3) , INTENT(in ) :: ctype ! momentum or tracers trends type 'DYN'/'TRA' INTEGER , INTENT(in ) :: kt ! time step !! INTEGER :: ji, jj, jk ! dummy loop indices REAL(wp), POINTER, DIMENSION(:,:) :: z2dx, z2dy, ztswu, ztswv ! 2D workspace REAL(wp), POINTER, DIMENSION(:,:,:) :: z3dx, z3dy ! 3D workspace !!---------------------------------------------------------------------- IF( lk_trdtra .AND. ctype == 'TRA' ) THEN ! active tracer trends ! !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added ! SELECT CASE( ktrd ) CASE( jptra_trd_xad ) ; CALL iom_put( "ttrd_xad", ptrdx ) ! x- horizontal advection CALL iom_put( "strd_xad", ptrdy ) CASE( jptra_trd_yad ) ; CALL iom_put( "ttrd_yad", ptrdx ) ! y- horizontal advection CALL iom_put( "strd_yad", ptrdy ) CASE( jptra_trd_zad ) ; CALL iom_put( "ttrd_zad", ptrdx ) ! z- vertical advection CALL iom_put( "strd_zad", ptrdy ) IF( .NOT.lk_vvl ) THEN ! cst volume : adv flux through z=0 surface z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) CALL iom_put( "ttrd_sad", z2dx ) CALL iom_put( "strd_sad", z2dy ) ENDIF CASE( jptra_trd_ldf ) ; CALL iom_put( "ttrd_ldf", ptrdx ) ! lateral diffusion CALL iom_put( "strd_ldf", ptrdy ) CASE( jptra_trd_zdf ) ; CALL iom_put( "ttrd_zdf", ptrdx ) ! vertical diffusion (including Kz contribution) CALL iom_put( "strd_zdf", ptrdy ) CASE( jptra_trd_dmp ) ; CALL iom_put( "ttrd_dmp", ptrdx ) ! internal restoring (damping) CALL iom_put( "strd_dmp", ptrdy ) CASE( jptra_trd_bbl ) ; CALL iom_put( "ttrd_bbl", ptrdx ) ! bottom boundary layer CALL iom_put( "strd_bbl", ptrdy ) CASE( jptra_trd_npc ) ; CALL iom_put( "ttrd_npc", ptrdx ) ! static instability mixing CALL iom_put( "strd_npc", ptrdy ) CASE( jptra_trd_qsr ) ; CALL iom_put( "ttrd_qsr", ptrdx ) ! penetrative solar radiat. (only on temperature) CASE( jptra_trd_nsr ) ; CALL iom_put( "ttrd_qns", ptrdx(:,:,1) ) ! non-solar radiation (only on temperature) CASE( jptra_trd_bbc ) ; CALL iom_put( "ttrd_bbc", ptrdx ) ! geothermal heating (only on temperature) END SELECT ENDIF IF( lk_trddyn .AND. ctype == 'DYN' ) THEN ! momentum trends ! ptrdx(:,:,:) = ptrdx(:,:,:) * umask(:,:,:) ! mask the trends ptrdy(:,:,:) = ptrdy(:,:,:) * vmask(:,:,:) !!gm NB : here a lbc_lnk should probably be added ! SELECT CASE( ktrd ) CASE( jpdyn_trd_hpg ) ; CALL iom_put( "utrd_hpg", ptrdx ) ! hydrostatic pressure gradient CALL iom_put( "vtrd_hpg", ptrdy ) CASE( jpdyn_trd_spg ) ; CALL iom_put( "utrd_spg", ptrdx ) ! surface pressure gradient CALL iom_put( "vtrd_spg", ptrdy ) CASE( jpdyn_trd_pvo ) ; CALL iom_put( "utrd_pvo", ptrdx ) ! planetary vorticity CALL iom_put( "vtrd_pvo", ptrdy ) CASE( jpdyn_trd_rvo ) ; CALL iom_put( "utrd_rvo", ptrdx ) ! relative vorticity (or metric term) CALL iom_put( "vtrd_rvo", ptrdy ) CASE( jpdyn_trd_keg ) ; CALL iom_put( "utrd_keg", ptrdx ) ! Kinetic Energy gradient (or had) CALL iom_put( "vtrd_keg", ptrdy ) z3dx(:,:,:) = 0._wp ! U.dxU & V.dyV (approximation) z3dy(:,:,:) = 0._wp DO jk = 1, jpkm1 ! no mask as un,vn are masked DO jj = 2, jpjm1 DO ji = 2, jpim1 z3dx(ji,jj,jk) = un(ji,jj,jk) * ( un(ji+1,jj,jk) - un(ji-1,jj,jk) ) / ( 2._wp * e1u(ji,jj) ) z3dy(ji,jj,jk) = vn(ji,jj,jk) * ( vn(ji,jj+1,jk) - vn(ji,jj-1,jk) ) / ( 2._wp * e2v(ji,jj) ) END DO END DO END DO CALL lbc_lnk( z3dx, 'U', -1. ) ; CALL lbc_lnk( z3dy, 'V', -1. ) CALL iom_put( "utrd_udx", z3dx ) CALL iom_put( "vtrd_vdy", z3dy ) CASE( jpdyn_trd_zad ) ; CALL iom_put( "utrd_zad", ptrdx ) ! vertical advection CALL iom_put( "vtrd_zad", ptrdy ) CASE( jpdyn_trd_ldf ) ; CALL iom_put( "utrd_ldf", ptrdx ) ! lateral diffusion CALL iom_put( "vtrd_ldf", ptrdy ) CASE( jpdyn_trd_zdf ) ; CALL iom_put( "utrd_zdf", ptrdx ) ! vertical diffusion CALL iom_put( "vtrd_zdf", ptrdy ) ! ! wind stress trends z2dx(:,:) = ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(:,:,1) * rau0 ) z2dy(:,:) = ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(:,:,1) * rau0 ) CALL iom_put( "utrd_tau", z2dx ) CALL iom_put( "vtrd_tau", z2dy ) CASE( jpdyn_trd_bfr ) ; CALL iom_put( "utrd_bfr", ptrdx ) ! bottom friction term CALL iom_put( "vtrd_bfr", ptrdy ) END SELECT ! ENDIF ! CALL wrk_dealloc( jpi, jpj , z2dx, z2dy, ztswu, ztswv ) CALL wrk_dealloc( jpi, jpj, jpk, z3dx, z3dy ) ! END SUBROUTINE trd_3Diom #else !!---------------------------------------------------------------------- !! Default case : Empty module No trend diagnostics !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt ) ! Empty routine REAL :: ptrdx(:,:,:), ptrdy(:,:,:) INTEGER :: ktrd, kt CHARACTER(len=3) :: ctype WRITE(*,*) 'trd_mod: You should not have seen this print! error ?', & & ptrdx(1,1,1), ptrdy(1,1,1), ktrd, ctype, kt 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/ ln_3D_trd_d, ln_KE_trd, ln_vor_trd, ln_ML_trd_d, & & ln_3D_trd_t, ln_PE_trd, ln_glo_trd, ln_ML_trd_t, & & nn_trd , cn_trdrst_in , ln_trdmld_restart, & & nn_ctls, cn_trdrst_out, ln_trdmld_instant, rn_ucf !!---------------------------------------------------------------------- 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,*) ' U & V trends: 3D output ln_3D_trd_d = ', ln_3D_trd_d WRITE(numout,*) ' T & S trends: 3D output ln_3D_trd_t = ', ln_3D_trd_t WRITE(numout,*) ' Kinetic Energy trends ln_KE_trd = ', ln_KE_trd WRITE(numout,*) ' Potential Energy trends ln_PE_trd = ', ln_PE_trd WRITE(numout,*) ' Barotropic vorticity trends ln_vor_trd = ', ln_vor_trd WRITE(numout,*) ' check domain averaged dyn & tra trends ln_glo_trd = ', ln_glo_trd WRITE(numout,*) ' U & V trends: Mixed Layer averaged ln_ML_trd_d = ', ln_3D_trd_d WRITE(numout,*) ' T & S trends: Mixed Layer averaged ln_ML_trd_t = ', ln_3D_trd_t ! WRITE(numout,*) ' frequency of trends diagnostics (glo) nn_trd = ', nn_trd WRITE(numout,*) ' control surface type (mld) nn_ctls = ', nn_ctls 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 rn_ucf = ', rn_ucf ENDIF ENDIF ! IF( ln_KE_trd .OR. ln_PE_trd .OR. ln_ML_trd_d ) & CALL ctl_stop( 'KE, PE, aur ML on momentum are not yet coded we stop' ) !!gm : Potential BUG : 3D output only for vector invariant form! add a ctl_stop or code the flux form case !!gm : bug/pb for vertical advection of tracer in vvl case: add T.dt[eta] in the output... ! 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