Skip to content
Snippets Groups Projects
Commit acd9004a authored by Andrew Coward's avatar Andrew Coward
Browse files

Merge branch...

Merge branch '120-tracer-conservation-for-configurations-with-forward-euler-passive-tracer-time-stepping-2' into 'main'

Resolve "Tracer conservation for configurations with forward Euler passive-tracer time stepping and time-varying grid-cell volumes" ('main')

Closes #120

See merge request nemo/nemo!227
parents 2591fbb4 ec0a2f51
No related branches found
No related tags found
No related merge requests found
......@@ -55,8 +55,6 @@ MODULE trabbl
REAL(wp), PUBLIC :: rn_ahtbbl !: along slope bbl diffusive coefficient [m2/s]
REAL(wp), PUBLIC :: rn_gambbl !: lateral coeff. for bottom boundary layer scheme [s]
LOGICAL , PUBLIC :: l_bbl !: flag to compute bbl diffu. flux coef and transport
REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: utr_bbl , vtr_bbl ! u- (v-) transport in the bottom boundary layer
REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: ahu_bbl , ahv_bbl ! masked diffusive bbl coeff. at u & v-pts
......@@ -117,8 +115,6 @@ CONTAINS
ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs)
ENDIF
IF( l_bbl ) CALL bbl( kt, nit000, 'TRA', Kbb, Kmm ) !* bbl coef. and transport (only if not already done in trcbbl)
IF( nn_bbl_ldf == 1 ) THEN !* Diffusive bbl
!
CALL tra_bbl_dif( pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts, Kmm )
......@@ -289,7 +285,7 @@ CONTAINS
END SUBROUTINE tra_bbl_adv
SUBROUTINE bbl( kt, kit000, cdtype, Kbb, Kmm )
SUBROUTINE bbl( kt, kit000, Kbb, Kmm )
!!----------------------------------------------------------------------
!! *** ROUTINE bbl ***
!!
......@@ -317,7 +313,6 @@ CONTAINS
!!----------------------------------------------------------------------
INTEGER , INTENT(in ) :: kt ! ocean time-step index
INTEGER , INTENT(in ) :: kit000 ! first time step index
CHARACTER(len=3), INTENT(in ) :: cdtype ! =TRA or TRC (tracer indicator)
INTEGER , INTENT(in ) :: Kbb, Kmm ! ocean time level index
!
INTEGER :: ji, jj ! dummy loop indices
......@@ -333,7 +328,7 @@ CONTAINS
IF( .NOT. l_istiled .OR. ntile == 1 ) THEN ! Do only on the first tile
IF( kt == kit000 ) THEN
IF(lwp) WRITE(numout,*)
IF(lwp) WRITE(numout,*) 'trabbl:bbl : Compute bbl velocities and diffusive coefficients in ', cdtype
IF(lwp) WRITE(numout,*) 'trabbl:bbl : Compute bbl velocities and diffusive coefficients'
IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
ENDIF
ENDIF
......@@ -479,8 +474,6 @@ CONTAINS
902 IF( ios > 0 ) CALL ctl_nam ( ios , 'nambbl in configuration namelist' )
IF(lwm) WRITE ( numond, nambbl )
!
l_bbl = .TRUE. !* flag to compute bbl coef and transport
!
IF(lwp) THEN !* Parameter control and print
WRITE(numout,*)
WRITE(numout,*) 'tra_bbl_init : bottom boundary layer initialisation'
......
......@@ -204,6 +204,10 @@ CONTAINS
IF( l_ldftra_time .OR. l_ldfeiv_time ) CALL ldf_tra( kstp, Nbb, Nnn ) ! and/or eiv coeff.
IF( l_ldfdyn_time ) CALL ldf_dyn( kstp, Nbb ) ! eddy viscosity coeff.
! BBL coefficients
!
IF( ln_trabbl ) CALL bbl( kstp, nit000, Nbb, Nnn ) ! BBL diffusion coefficients and transports
!>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
! Ocean dynamics : hdiv, ssh, e3, u, v, w
!<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
......
......@@ -249,6 +249,10 @@ CONTAINS
! ! Advective velocity needed for tracers advection - already computed if ln_dynadv_vec=F
IF( ln_dynadv_vec ) CALL wzv ( kstp, Kbb, Kmm, Kaa, zaU, zaV, ww )
!
! ! BBL coefficients required for both passive- and active-tracer transport within
! ! the BBL (stage 3 only, requires uu, vv, gdept at Kmm)
IF( ( kstg == 3 ) .AND. ln_trabbl ) CALL bbl( kstp, nit000, Kbb, Kmm )
!
# if defined key_top
! !== Passive Tracer ==!
!
......
......@@ -55,11 +55,6 @@ CONTAINS
!
IF( ln_timing ) CALL timing_start('trc_bbl')
!
IF( .NOT. l_offline ) THEN
CALL bbl( kt, nittrc000, 'TRC', Kbb, Kmm ) ! Online coupling with dynamics : Computation of bbl coef and bbl transport
l_bbl = .FALSE. ! Offline coupling with dynamics : Read bbl coef and bbl transport from input files
ENDIF
IF( l_trdtrc ) THEN
ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) ) ! temporary save of trends
ztrtrd(:,:,:,:) = ptr(:,:,:,:,Krhs)
......
......@@ -372,7 +372,7 @@ CONTAINS
ENDIF
!
DO jk = 1, jpk
zvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Krhs) * tmask(:,:,jk)
zvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk)
END DO
!
DO jn = 1, jptra
......
......@@ -60,6 +60,7 @@ CONTAINS
INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices
!
INTEGER :: jk, jn ! dummy loop indices
INTEGER :: ibb ! local time-level index
REAL(wp):: ztrai ! local scalar
LOGICAL :: ll_trcstat ! local logical
CHARACTER (len=25) :: charout !
......@@ -67,8 +68,10 @@ CONTAINS
!
IF( ln_timing ) CALL timing_start('trc_stp')
!
ibb = Kbb ! default "before" time-level index
IF( l_1st_euler .OR. ln_top_euler ) THEN ! at nittrc000
rDt_trc = rn_Dt ! = rn_Dt (use or restarting with Euler time stepping)
ibb = Kmm ! time-level index used to substitute the "before" with the "now" time level
ELSEIF( kt <= nittrc000 + 1 ) THEN ! at nittrc000 or nittrc000+1
rDt_trc = 2. * rn_Dt ! = 2 rn_Dt (leapfrog)
ENDIF
......@@ -98,9 +101,9 @@ CONTAINS
CALL trc_rst_opn ( kt ) ! Open tracer restart file
IF( lrst_trc ) CALL trc_rst_cal ( kt, 'WRITE' ) ! calendar
CALL trc_wri ( kt, Kmm ) ! output of passive tracers with iom I/O manager
CALL trc_sms ( kt, Kbb, Kmm, Krhs ) ! tracers: sinks and sources
CALL trc_sms ( kt, ibb, Kmm, Krhs ) ! tracers: sinks and sources
#if ! defined key_sed_off
CALL trc_trp ( kt, Kbb, Kmm, Krhs, Kaa ) ! transport of passive tracers
CALL trc_trp ( kt, ibb, Kmm, Krhs, Kaa ) ! transport of passive tracers
#endif
!
! Note passive tracers have been time-filtered in trc_trp but the time level
......@@ -123,7 +126,7 @@ CONTAINS
tr(:,:,:,:,Kmm) = tr(:,:,:,:,Kaa)
ENDIF
!
IF( lrst_trc ) CALL trc_rst_wri ( kt, Kbb, Kmm, Kaa ) ! write tracer restart file
IF( lrst_trc ) CALL trc_rst_wri ( kt, ibb, Kmm, Kaa ) ! write tracer restart file
! IF( lrst_trc ) CALL trc_rst_wri ( kt, Kmm, Kaa, Kbb ) ! write tracer restart file
!
IF (ll_trcstat) THEN
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment