MODULE traadv !!============================================================================== !! *** MODULE traadv *** !! Ocean active tracers: advection trend !!============================================================================== !! History : 2.0 ! 2005-11 (G. Madec) Original code !! 3.3 ! 2010-09 (C. Ethe, G. Madec) merge TRC-TRA + switch from velocity to transport !! 3.6 ! 2011-06 (G. Madec) Addition of Mixed Layer Eddy parameterisation !! 3.7 ! 2014-05 (G. Madec) Add 2nd/4th order cases for CEN and FCT schemes !! - ! 2014-12 (G. Madec) suppression of cross land advection option !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tra_adv : compute ocean tracer advection trend !! tra_adv_ctl : control the different options of advection scheme !!---------------------------------------------------------------------- USE oce ! ocean dynamics and active tracers USE dom_oce ! ocean space and time domain USE domvvl ! variable vertical scale factors USE traadv_cen ! centered scheme (tra_adv_cen routine) USE traadv_fct ! FCT scheme (tra_adv_fct routine) USE traadv_mus ! MUSCL scheme (tra_adv_mus routine) USE traadv_ubs ! UBS scheme (tra_adv_ubs routine) USE traadv_qck ! QUICKEST scheme (tra_adv_qck routine) USE traadv_mle ! ML eddy induced velocity (tra_adv_mle routine) USE ldftra ! lateral diffusion: eddy diffusivity & EIV coeff. USE ldfslp ! Lateral diffusion: slopes of neutral surfaces USE c1d ! 1D vertical configuration ! USE in_out_manager ! I/O manager USE iom ! I/O module USE prtctl ! Print control USE lib_mpp ! MPP library USE wrk_nemo ! Memory Allocation USE timing ! Timing USE diaptr ! Poleward heat transport IMPLICIT NONE PRIVATE PUBLIC tra_adv ! routine called by step module PUBLIC tra_adv_init ! routine called by opa module ! !!* Namelist namtra_adv * LOGICAL :: ln_traadv_cen ! centered scheme flag INTEGER :: nn_cen_h, nn_cen_v ! =2/4 : horizontal and vertical choices of the order of CEN scheme LOGICAL :: ln_traadv_fct ! FCT scheme flag INTEGER :: nn_fct_h, nn_fct_v ! =2/4 : horizontal and vertical choices of the order of FCT scheme INTEGER :: nn_fct_zts ! >=1 : 2nd order FCT with vertical sub-timestepping LOGICAL :: ln_traadv_mus ! MUSCL scheme flag LOGICAL :: ln_mus_ups ! use upstream scheme in vivcinity of river mouths LOGICAL :: ln_traadv_ubs ! UBS scheme flag INTEGER :: nn_ubs_v ! =2/4 : vertical choice of the order of UBS scheme LOGICAL :: ln_traadv_qck ! QUICKEST scheme flag INTEGER :: nadv ! choice of the type of advection scheme ! ! ! associated indices: INTEGER, PARAMETER :: np_NO_adv = 0 ! no T-S advection INTEGER, PARAMETER :: np_CEN = 1 ! 2nd/4th order centered scheme INTEGER, PARAMETER :: np_FCT = 2 ! 2nd/4th order Flux Corrected Transport scheme INTEGER, PARAMETER :: np_FCT_zts = 3 ! 2nd order FCT scheme with vertical sub-timestepping INTEGER, PARAMETER :: np_MUS = 4 ! MUSCL scheme INTEGER, PARAMETER :: np_UBS = 5 ! 3rd order Upstream Biased Scheme INTEGER, PARAMETER :: np_QCK = 6 ! QUICK scheme !! * Substitutions # include "domzgr_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/OPA 3.7 , NEMO Consortium (2014) !! $Id$ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tra_adv( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_adv *** !! !! ** Purpose : compute the ocean tracer advection trend. !! !! ** Method : - Update (ua,va) with the advection term following nadv !!---------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step index ! INTEGER :: jk ! dummy loop index REAL(wp), POINTER, DIMENSION(:,:,:) :: zun, zvn, zwn !!---------------------------------------------------------------------- ! IF( nn_timing == 1 ) CALL timing_start('tra_adv') ! CALL wrk_alloc( jpi,jpj,jpk, zun, zvn, zwn ) ! ! ! set time step IF( neuler == 0 .AND. kt == nit000 ) THEN ! at nit000 r2dtra(:) = rdttra(:) ! = rdtra (restarting with Euler time stepping) ELSEIF( kt <= nit000 + 1) THEN ! at nit000 or nit000+1 r2dtra(:) = 2._wp * rdttra(:) ! = 2 rdttra (leapfrog) ENDIF ! ! !== effective transport ==! DO jk = 1, jpkm1 zun(:,:,jk) = e2u (:,:) * fse3u(:,:,jk) * un(:,:,jk) ! eulerian transport only zvn(:,:,jk) = e1v (:,:) * fse3v(:,:,jk) * vn(:,:,jk) zwn(:,:,jk) = e1e2t(:,:) * wn(:,:,jk) END DO ! IF( ln_vvl_ztilde .OR. ln_vvl_layer ) THEN ! add z-tilde and/or vvl corrections zun(:,:,:) = zun(:,:,:) + un_td(:,:,:) zvn(:,:,:) = zvn(:,:,:) + vn_td(:,:,:) ENDIF ! zun(:,:,jpk) = 0._wp ! no transport trough the bottom zvn(:,:,jpk) = 0._wp zwn(:,:,jpk) = 0._wp ! IF( ln_ldfeiv .AND. .NOT. ln_traldf_triad ) & & CALL ldf_eiv_trp( kt, nit000, zun, zvn, zwn, 'TRA' ) ! add the eiv transport (if necessary) ! IF( ln_mle ) CALL tra_adv_mle( kt, nit000, zun, zvn, zwn, 'TRA' ) ! add the mle transport (if necessary) ! CALL iom_put( "uocetr_eff", zun ) ! output effective transport CALL iom_put( "vocetr_eff", zvn ) CALL iom_put( "wocetr_eff", zwn ) ! !!gm ??? IF( ln_diaptr ) CALL dia_ptr( zvn ) ! diagnose the effective MSF !!gm ??? ! SELECT CASE ( nadv ) !== compute advection trend and add it to general trend ==! ! CASE ( np_CEN ) ! Centered scheme : 2nd / 4th order CALL tra_adv_cen ( kt, nit000, 'TRA', zun, zvn, zwn , tsn, tsa, jpts, nn_cen_h, nn_cen_v ) CASE ( np_FCT ) ! FCT scheme : 2nd / 4th order CALL tra_adv_fct ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts, nn_fct_h, nn_fct_v ) CASE ( np_FCT_zts ) ! 2nd order FCT with vertical time-splitting CALL tra_adv_fct_zts( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts , nn_fct_zts ) CASE ( np_MUS ) ! MUSCL CALL tra_adv_mus ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsa, jpts , ln_mus_ups ) CASE ( np_UBS ) ! UBS CALL tra_adv_ubs ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts , nn_ubs_v ) CASE ( np_QCK ) ! QUICKEST CALL tra_adv_qck ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts ) ! END SELECT ! ! ! print mean trends (used for debugging) IF(ln_ctl) CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv - Ta: ', mask1=tmask, & & tab3d_2=tsa(:,:,:,jp_sal), clinfo2= ' Sa: ', mask2=tmask, clinfo3='tra' ) ! IF( nn_timing == 1 ) CALL timing_stop( 'tra_adv' ) ! CALL wrk_dealloc( jpi,jpj,jpk, zun, zvn, zwn ) ! END SUBROUTINE tra_adv SUBROUTINE tra_adv_init !!--------------------------------------------------------------------- !! *** ROUTINE tra_adv_init *** !! !! ** Purpose : Control the consistency between namelist options for !! tracer advection schemes and set nadv !!---------------------------------------------------------------------- INTEGER :: ioptio, ios ! Local integers ! NAMELIST/namtra_adv/ ln_traadv_cen, nn_cen_h, nn_cen_v, & ! CEN & ln_traadv_fct, nn_fct_h, nn_fct_v, nn_fct_zts, & ! FCT & ln_traadv_mus, ln_mus_ups, & ! MUSCL & ln_traadv_ubs, nn_ubs_v, & ! UBS & ln_traadv_qck ! QCK !!---------------------------------------------------------------------- ! ! !== Namelist ==! ! REWIND( numnam_ref ) ! Namelist namtra_adv in reference namelist : Tracer advection scheme READ ( numnam_ref, namtra_adv, IOSTAT = ios, ERR = 901) 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv in reference namelist', lwp ) ! REWIND( numnam_cfg ) ! Namelist namtra_adv in configuration namelist : Tracer advection scheme READ ( numnam_cfg, namtra_adv, IOSTAT = ios, ERR = 902 ) 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv in configuration namelist', lwp ) IF(lwm) WRITE ( numond, namtra_adv ) IF(lwp) THEN ! Namelist print WRITE(numout,*) WRITE(numout,*) 'tra_adv_init : choice/control of the tracer advection scheme' WRITE(numout,*) '~~~~~~~~~~~' WRITE(numout,*) ' Namelist namtra_adv : chose a advection scheme for tracers' WRITE(numout,*) ' centered scheme ln_traadv_cen = ', ln_traadv_cen WRITE(numout,*) ' horizontal 2nd/4th order nn_cen_h = ', nn_fct_h WRITE(numout,*) ' vertical 2nd/4th order nn_cen_v = ', nn_fct_v WRITE(numout,*) ' Flux Corrected Transport scheme ln_traadv_fct = ', ln_traadv_fct WRITE(numout,*) ' horizontal 2nd/4th order nn_fct_h = ', nn_fct_h WRITE(numout,*) ' vertical 2nd/4th order nn_fct_v = ', nn_fct_v WRITE(numout,*) ' 2nd order + vertical sub-timestepping nn_fct_zts = ', nn_fct_zts WRITE(numout,*) ' MUSCL scheme ln_traadv_mus = ', ln_traadv_mus WRITE(numout,*) ' + upstream scheme near river mouths ln_mus_ups = ', ln_mus_ups WRITE(numout,*) ' UBS scheme ln_traadv_ubs = ', ln_traadv_ubs WRITE(numout,*) ' vertical 2nd/4th order nn_ubs_v = ', nn_ubs_v WRITE(numout,*) ' QUICKEST scheme ln_traadv_qck = ', ln_traadv_qck ENDIF ioptio = 0 !== Parameter control ==! IF( ln_traadv_cen ) ioptio = ioptio + 1 IF( ln_traadv_fct ) ioptio = ioptio + 1 IF( ln_traadv_mus ) ioptio = ioptio + 1 IF( ln_traadv_ubs ) ioptio = ioptio + 1 IF( ln_traadv_qck ) ioptio = ioptio + 1 ! IF( ioptio == 0 ) THEN nadv = np_NO_adv CALL ctl_warn( 'tra_adv_init: You are running without tracer advection.' ) ENDIF IF( (ioptio /= 1).AND. (.NOT. lk_c1d ) ) & CALL ctl_stop( 'tra_adv_init: Choose ONE advection scheme in namelist namtra_adv' ) ! IF( ln_traadv_cen .AND. ( nn_cen_h /= 2 .AND. nn_cen_h /= 4 ) & ! Centered .AND. ( nn_cen_v /= 2 .AND. nn_cen_v /= 4 ) ) THEN CALL ctl_stop( 'tra_adv_init: CEN scheme, choose 2nd or 4th order' ) ENDIF IF( ln_traadv_fct .AND. ( nn_fct_h /= 2 .AND. nn_fct_h /= 4 ) & ! FCT .AND. ( nn_fct_v /= 2 .AND. nn_fct_v /= 4 ) ) THEN CALL ctl_stop( 'tra_adv_init: FCT scheme, choose 2nd or 4th order' ) ENDIF IF( ln_traadv_fct .AND. nn_fct_zts > 0 ) THEN IF( nn_fct_h == 4 ) THEN nn_fct_h = 2 CALL ctl_stop( 'tra_adv_init: force 2nd order FCT scheme, 4th order does not exist with sub-timestepping' ) ENDIF IF( lk_vvl ) THEN CALL ctl_stop( 'tra_adv_init: vertical sub-timestepping not allow in non-linear free surface' ) ENDIF IF( nn_fct_zts == 1 ) CALL ctl_warn( 'tra_adv_init: FCT with ONE sub-timestep = FCT without sub-timestep' ) ENDIF IF( ln_traadv_ubs .AND. ( nn_ubs_v /= 2 .AND. nn_ubs_v /= 4 ) ) THEN ! UBS CALL ctl_stop( 'tra_adv_init: UBS scheme, choose 2nd or 4th order' ) ENDIF IF( ln_traadv_ubs .AND. nn_ubs_v == 4 ) THEN CALL ctl_warn( 'tra_adv_init: UBS scheme, only 2nd FCT scheme available on the vertical. It will be used' ) ENDIF IF( ln_isfcav ) THEN ! ice-shelf cavities IF( ln_traadv_cen .AND. nn_cen_v /= 4 .OR. & ! NO 4th order with ISF & ln_traadv_fct .AND. nn_fct_v /= 4 ) CALL ctl_stop( 'tra_adv_init: 4th order COMPACT scheme not allowed with ISF' ) ENDIF ! ! !== used advection scheme ==! ! ! set nadv IF( ln_traadv_cen ) nadv = np_CEN IF( ln_traadv_fct ) nadv = np_FCT IF( ln_traadv_fct .AND. nn_fct_zts > 0 ) nadv = np_FCT_zts IF( ln_traadv_mus ) nadv = np_MUS IF( ln_traadv_ubs ) nadv = np_UBS IF( ln_traadv_qck ) nadv = np_QCK IF(lwp) THEN ! Print the choice WRITE(numout,*) IF( nadv == np_NO_adv ) WRITE(numout,*) ' NO T-S advection' IF( nadv == np_CEN ) WRITE(numout,*) ' CEN scheme is used. Horizontal order: ', nn_cen_h, & & ' Vertical order: ', nn_cen_v IF( nadv == np_FCT ) WRITE(numout,*) ' FCT scheme is used. Horizontal order: ', nn_fct_h, & & ' Vertical order: ', nn_fct_v IF( nadv == np_FCT_zts ) WRITE(numout,*) ' use 2nd order FCT with ', nn_fct_zts,'vertical sub-timestepping' IF( nadv == np_MUS ) WRITE(numout,*) ' MUSCL scheme is used' IF( nadv == np_UBS ) WRITE(numout,*) ' UBS scheme is used' IF( nadv == np_QCK ) WRITE(numout,*) ' QUICKEST scheme is used' ENDIF ! CALL tra_adv_mle_init !== initialisation of the Mixed Layer Eddy parametrisation (MLE) ==! ! END SUBROUTINE tra_adv_init !!====================================================================== END MODULE traadv