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/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/TOP/AGE – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/TOP/AGE/trcsms_age.F90 @ 14221

Last change on this file since 14221 was 14221, checked in by mcastril, 4 years ago

Revert changes unrelated with MP

  • Property svn:keywords set to Id
File size: 3.4 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#  include "single_precision_substitute.h90" 
32
33   !!----------------------------------------------------------------------
34   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
35   !! $Id$
36   !! Software governed by the CeCILL license (see ./LICENSE)
37   !!----------------------------------------------------------------------
38CONTAINS
39
40   SUBROUTINE trc_sms_age( kt, Kbb, Kmm, Krhs )
41      !!----------------------------------------------------------------------
42      !!                     ***  trc_sms_age  ***
43      !!
44      !! ** Purpose :   main routine of AGE model
45      !!
46      !! ** Method  : -
47      !!----------------------------------------------------------------------
48      INTEGER, INTENT(in) ::   kt              ! ocean time-step index
49      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! ocean time level
50      INTEGER ::   jn, jk   ! dummy loop index
51      !!----------------------------------------------------------------------
52      !
53      IF( ln_timing )   CALL timing_start('trc_sms_age')
54      !
55      IF(lwp) WRITE(numout,*)
56      IF(lwp) WRITE(numout,*) ' trc_sms_age:  AGE model'
57      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
58
59      IF( l_1st_euler .OR. ln_top_euler ) THEN
60         tr(:,:,:,jp_age,Kbb) = tr(:,:,:,jp_age,Kmm)
61      ENDIF
62
63
64      DO jk = 1, nla_age
65         tr(:,:,jk,jp_age,Krhs) = rn_age_kill_rate * tr(:,:,jk,jp_age,Kbb)
66      END DO
67      !
68      tr(:,:,nl_age,jp_age,Krhs) = frac_kill_age * rn_age_kill_rate * tr(:,:,nl_age,jp_age,Kbb)  &
69          &                   + frac_add_age  * rryear * tmask(:,:,nl_age)
70      !
71      DO jk = nlb_age, jpk
72         tr(:,:,jk,jp_age,Krhs) = tmask(:,:,jk) * rryear
73      END DO
74      !
75      IF( l_trdtrc ) CALL trd_trc( tr(:,:,:,jp_age,Krhs), jn, jptra_sms, kt, Kmm )   ! save trends
76      !
77      IF( ln_timing )   CALL timing_stop('trc_sms_age')
78      !
79   END SUBROUTINE trc_sms_age
80
81   !!======================================================================
82END MODULE trcsms_age
Note: See TracBrowser for help on using the repository browser.