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_my_trc.F90 in branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC – NEMO

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcsms_my_trc.F90 @ 5601

Last change on this file since 5601 was 5601, checked in by cbricaud, 9 years ago

commit changes/bugfix/... for crs ; ok with time-splitting/fixed volume

  • Property svn:keywords set to Id
File size: 5.1 KB
RevLine 
[932]1MODULE trcsms_my_trc
2   !!======================================================================
3   !!                         ***  MODULE trcsms_my_trc  ***
4   !! TOP :   Main module of the MY_TRC tracers
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) Original code
7   !!----------------------------------------------------------------------
8#if defined key_my_trc
9   !!----------------------------------------------------------------------
10   !!   'key_my_trc'                                               CFC tracers
11   !!----------------------------------------------------------------------
[3294]12   !! trc_sms_my_trc       : MY_TRC model main routine
[2715]13   !! trc_sms_my_trc_alloc : allocate arrays specific to MY_TRC sms
[932]14   !!----------------------------------------------------------------------
15   USE par_trc         ! TOP parameters
[1255]16   USE oce_trc         ! Ocean variables
17   USE trc             ! TOP variables
[4990]18   USE trd_oce
19   USE trdtrc
[932]20
21   IMPLICIT NONE
22   PRIVATE
23
[2715]24   PUBLIC   trc_sms_my_trc       ! called by trcsms.F90 module
25   PUBLIC   trc_sms_my_trc_alloc ! called by trcini_my_trc.F90 module
[932]26
[5601]27   INTEGER , PUBLIC :: nl_age                         ! T level surrounding age_depth
28   INTEGER , PUBLIC :: nla_age                        ! T level wholly above age_depth
29   INTEGER , PUBLIC :: nlb_age                        ! T level wholly below age_depth
30
31   REAL(wp), PUBLIC ::   rryear                    !: recip number of seconds in one year
32   REAL(wp), PUBLIC ::   age_depth = 10.           !: depth over which age tracer reset to zero
33   REAL(wp), PUBLIC ::   age_kill_rate = -1./7200. !: recip of relaxation timescale (s) for  age tracer shallower than age_depth
34   REAL(wp), PUBLIC ::   frac_kill_age             !: fraction of level nl_age above age_depth where it is relaxed towards zero
35   REAL(wp), PUBLIC ::   frac_add_age              !: fraction of level nl_age below age_depth where it is incremented
36
37
[2715]38   ! Defined HERE the arrays specific to MY_TRC sms and ALLOCATE them in trc_sms_my_trc_alloc
[3294]39
[932]40   !!----------------------------------------------------------------------
[2528]41   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[3294]42   !! $Id$
[2715]43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[932]44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE trc_sms_my_trc( kt )
48      !!----------------------------------------------------------------------
[3294]49      !!                     ***  trc_sms_my_trc  ***
[932]50      !!
51      !! ** Purpose :   main routine of MY_TRC model
52      !!
[3294]53      !! ** Method  : -
[932]54      !!----------------------------------------------------------------------
[2715]55      !
56      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
[5601]57      INTEGER ::   jn, jk   ! dummy loop index
[3294]58      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrmyt
59!!----------------------------------------------------------------------
60      !
61      IF( nn_timing == 1 )  CALL timing_start('trc_sms_my_trc')
62      !
[932]63      IF(lwp) WRITE(numout,*)
64      IF(lwp) WRITE(numout,*) ' trc_sms_my_trc:  MY_TRC model'
65      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
[1162]66
[3294]67      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrmyt )
68
[5601]69      DO jk = 1, nla_age
70         tra(:,:,jk,jpmyt1) = age_kill_rate * trb(:,:,jk,jpmyt1)
71      ENDDO
72      !
73      tra(:,:,nl_age,jpmyt1) = frac_kill_age * age_kill_rate * trb(:,:,nl_age,jpmyt1)  &
74          &                  + frac_add_age  * rryear * tmask(:,:,nl_age)
75      !
76      DO jk = nlb_age, jpk
77         tra(:,:,jk,jpmyt1) = tmask(:,:,jk) * rryear
78      ENDDO
79      !
[2715]80      IF( l_trdtrc ) THEN      ! Save the trends in the ixed layer
[1255]81          DO jn = jp_myt0, jp_myt1
82            ztrmyt(:,:,:) = tra(:,:,:,jn)
[4990]83            CALL trd_trc( ztrmyt, jn, jptra_sms, kt )   ! save trends
[1255]84          END DO
[3294]85          CALL wrk_dealloc( jpi, jpj, jpk, ztrmyt )
[1255]86      END IF
[932]87      !
[3294]88      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_my_trc')
89      !
[932]90   END SUBROUTINE trc_sms_my_trc
[2715]91
92
93   INTEGER FUNCTION trc_sms_my_trc_alloc()
94      !!----------------------------------------------------------------------
95      !!              ***  ROUTINE trc_sms_my_trc_alloc  ***
96      !!----------------------------------------------------------------------
97      !
98      ! ALLOCATE here the arrays specific to MY_TRC
99      ! ALLOCATE( tab(...) , STAT=trc_sms_my_trc_alloc )
100      trc_sms_my_trc_alloc = 0      ! set to zero if no array to be allocated
101      !
102      IF( trc_sms_my_trc_alloc /= 0 ) CALL ctl_warn('trc_sms_my_trc_alloc : failed to allocate arrays')
103      !
104   END FUNCTION trc_sms_my_trc_alloc
105
106
[932]107#else
108   !!----------------------------------------------------------------------
109   !!   Dummy module                                        No MY_TRC model
110   !!----------------------------------------------------------------------
111CONTAINS
112   SUBROUTINE trc_sms_my_trc( kt )             ! Empty routine
113      INTEGER, INTENT( in ) ::   kt
114      WRITE(*,*) 'trc_sms_my_trc: You should not have seen this print! error?', kt
115   END SUBROUTINE trc_sms_my_trc
116#endif
117
118   !!======================================================================
119END MODULE trcsms_my_trc
Note: See TracBrowser for help on using the repository browser.