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 branches/UKMO/dev_r10171_test_crs_AMM7/NEMOGCM/NEMO/TOP_SRC/AGE – NEMO

source: branches/UKMO/dev_r10171_test_crs_AMM7/NEMOGCM/NEMO/TOP_SRC/AGE/trcsms_age.F90 @ 10207

Last change on this file since 10207 was 10207, checked in by cmao, 6 years ago

remove svn keyword

  • Property svn:executable set to *
File size: 4.1 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#if defined key_age
9   !!----------------------------------------------------------------------
10   !!   'key_age'                                               AGE tracer
11   !!----------------------------------------------------------------------
12   !! trc_sms_age       : AGE model main routine
13   !!----------------------------------------------------------------------
14   USE oce_trc         ! Ocean variables
15   USE trc             ! TOP variables
16   USE trd_oce
17   USE trdtrc
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   trc_sms_age       ! called by trcsms.F90 module
23
24   INTEGER , PUBLIC :: nl_age             ! T level surrounding age_depth
25   INTEGER , PUBLIC :: nla_age            ! T level wholly above age_depth
26   INTEGER , PUBLIC :: nlb_age            ! T level wholly below age_depth
27
28   REAL(wp), PUBLIC :: rn_age_depth       ! = 10       depth over which age tracer reset to zero
29   REAL(wp), PUBLIC :: rn_age_kill_rate   ! = -1./7200  recip of relaxation timescale (s) for  age tracer shallower than age_depth
30   
31   REAL(wp), PUBLIC :: rryear          !: recip number of seconds in one year
32   REAL(wp), PUBLIC :: frac_kill_age   !: fraction of level nl_age above age_depth where it is relaxed towards zero
33   REAL(wp), PUBLIC :: frac_add_age    !: fraction of level nl_age below age_depth where it is incremented
34
35
36   !!----------------------------------------------------------------------
37   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
38   !! $Id$
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE trc_sms_age( kt )
44      !!----------------------------------------------------------------------
45      !!                     ***  trc_sms_age  ***
46      !!
47      !! ** Purpose :   main routine of AGE model
48      !!
49      !! ** Method  : -
50      !!----------------------------------------------------------------------
51      !
52      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
53      INTEGER ::   jn, jk   ! dummy loop index
54      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrage
55      !!----------------------------------------------------------------------
56      !
57      IF( nn_timing == 1 )  CALL timing_start('trc_sms_age')
58      !
59      IF(lwp) WRITE(numout,*)
60      IF(lwp) WRITE(numout,*) ' trc_sms_age:  AGE model'
61      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
62
63      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrage )
64
65      DO jk = 1, nla_age
66         tra(:,:,jk,jpage1) = rn_age_kill_rate * trb(:,:,jk,jpage1)
67      ENDDO
68      !
69      tra(:,:,nl_age,jpage1) = frac_kill_age * rn_age_kill_rate * trb(:,:,nl_age,jpage1)  &
70          &                  + frac_add_age  * rryear * tmask(:,:,nl_age)
71      !
72      DO jk = nlb_age, jpk
73         tra(:,:,jk,jpage1) = tmask(:,:,jk) * rryear
74      ENDDO
75      !
76      IF( l_trdtrc ) THEN      ! Save the trends in the ixed layer
77          DO jn = jp_age0, jp_age1
78            ztrage(:,:,:) = tra(:,:,:,jn)
79            CALL trd_trc( ztrage, jn, jptra_sms, kt )   ! save trends
80          END DO
81          CALL wrk_dealloc( jpi, jpj, jpk, ztrage )
82      END IF
83      !
84      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_age')
85      !
86   END SUBROUTINE trc_sms_age
87
88#else
89   !!----------------------------------------------------------------------
90   !!   Dummy module                                        No AGE model
91   !!----------------------------------------------------------------------
92CONTAINS
93   SUBROUTINE trc_sms_age( kt )             ! Empty routine
94      INTEGER, INTENT( in ) ::   kt
95      WRITE(*,*) 'trc_sms_age: You should not have seen this print! error?', kt
96   END SUBROUTINE trc_sms_age
97#endif
98
99   !!======================================================================
100END MODULE trcsms_age
Note: See TracBrowser for help on using the repository browser.