New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcsms_age.F90 in NEMO/trunk/src/TOP/AGE – NEMO

source: NEMO/trunk/src/TOP/AGE/trcsms_age.F90 @ 14325

Last change on this file since 14325 was 14173, checked in by cetlod, 3 years ago

Bugfix to ensure restartability of AGE tracer when using euler time-stepping in TOP

  • Property svn:keywords set to Id
File size: 3.3 KB
Line 
1MODULE trcsms_age
2   !!======================================================================
3   !!                         ***  MODULE trcsms_age  ***
4   !! TOP :   Main module of the AGE tracers
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) Original code
7   !!----------------------------------------------------------------------
8   !! trc_sms_age       : AGE model main routine
9   !!----------------------------------------------------------------------
10   USE oce_trc         ! Ocean variables
11   USE trc             ! TOP variables
12   USE trd_oce
13   USE trdtrc
14
15   IMPLICIT NONE
16   PRIVATE
17
18   PUBLIC   trc_sms_age       ! called by trcsms.F90 module
19
20   INTEGER , PUBLIC :: nl_age             ! T level surrounding age_depth
21   INTEGER , PUBLIC :: nla_age            ! T level wholly above age_depth
22   INTEGER , PUBLIC :: nlb_age            ! T level wholly below age_depth
23
24   REAL(wp), PUBLIC :: rn_age_depth       ! = 10       depth over which age tracer reset to zero
25   REAL(wp), PUBLIC :: rn_age_kill_rate   ! = -1./7200  recip of relaxation timescale (s) for  age tracer shallower than age_depth
26   
27   REAL(wp), PUBLIC :: rryear          !: recip number of seconds in one year
28   REAL(wp), PUBLIC :: frac_kill_age   !: fraction of level nl_age above age_depth where it is relaxed towards zero
29   REAL(wp), PUBLIC :: frac_add_age    !: fraction of level nl_age below age_depth where it is incremented
30
31
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE trc_sms_age( kt, Kbb, Kmm, Krhs )
40      !!----------------------------------------------------------------------
41      !!                     ***  trc_sms_age  ***
42      !!
43      !! ** Purpose :   main routine of AGE model
44      !!
45      !! ** Method  : -
46      !!----------------------------------------------------------------------
47      INTEGER, INTENT(in) ::   kt              ! ocean time-step index
48      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! ocean time level
49      INTEGER ::   jn, jk   ! dummy loop index
50      !!----------------------------------------------------------------------
51      !
52      IF( ln_timing )   CALL timing_start('trc_sms_age')
53      !
54      IF(lwp) WRITE(numout,*)
55      IF(lwp) WRITE(numout,*) ' trc_sms_age:  AGE model'
56      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
57
58      IF( l_1st_euler .OR. ln_top_euler ) THEN
59         tr(:,:,:,jp_age,Kbb) = tr(:,:,:,jp_age,Kmm)
60      ENDIF
61
62
63      DO jk = 1, nla_age
64         tr(:,:,jk,jp_age,Krhs) = rn_age_kill_rate * tr(:,:,jk,jp_age,Kbb)
65      END DO
66      !
67      tr(:,:,nl_age,jp_age,Krhs) = frac_kill_age * rn_age_kill_rate * tr(:,:,nl_age,jp_age,Kbb)  &
68          &                   + frac_add_age  * rryear * tmask(:,:,nl_age)
69      !
70      DO jk = nlb_age, jpk
71         tr(:,:,jk,jp_age,Krhs) = tmask(:,:,jk) * rryear
72      END DO
73      !
74      IF( l_trdtrc ) CALL trd_trc( tr(:,:,:,jp_age,Krhs), jn, jptra_sms, kt, Kmm )   ! save trends
75      !
76      IF( ln_timing )   CALL timing_stop('trc_sms_age')
77      !
78   END SUBROUTINE trc_sms_age
79
80   !!======================================================================
81END MODULE trcsms_age
Note: See TracBrowser for help on using the repository browser.