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.
trcnam_age.F90 in NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/AGE – NEMO

source: NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/AGE/trcnam_age.F90 @ 10115

Last change on this file since 10115 was 10115, checked in by cbricaud, 6 years ago

phase 3.6 coarsening branch with nemo_3.6_rev9192

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1MODULE trcnam_age
2   !!======================================================================
3   !!                         ***  MODULE trcnam_age  ***
4   !! TOP :   initialisation of some run parameters for Age tracer
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec)
7   !!----------------------------------------------------------------------
8#if defined key_age
9   !!----------------------------------------------------------------------
10   !!   'key_age'                                               AGE tracers
11   !!----------------------------------------------------------------------
12   !! trc_nam_age      : AGE  tracer initialisation
13   !!----------------------------------------------------------------------
14   USE oce_trc         ! Ocean variables
15   USE trcsms_age      ! AGE specific variable
16   USE trc
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   trc_nam_age   ! called by trcnam.F90 module
22
23   !!----------------------------------------------------------------------
24   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
25   !! $Id$
26   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
27   !!----------------------------------------------------------------------
28
29CONTAINS
30
31   SUBROUTINE trc_nam_age
32      !!-------------------------------------------------------------------
33      !!                  ***  ROUTINE trc_nam_age  ***
34      !!                 
35      !! ** Purpose :   Definition some run parameter for AGE model
36      !!
37      !! ** input   :   Namelist namage
38      !!----------------------------------------------------------------------
39      INTEGER ::  numnatg_ref = -1   ! Logical unit for reference AGE namelist
40      INTEGER ::  numnatg_cfg = -1   ! Logical unit for configuration AGE namelist
41      INTEGER ::  numong      = -1   ! Logical unit for output namelist
42      INTEGER :: ios                 ! Local integer output status for namelist read
43      INTEGER :: jl, jn
44      !!
45      NAMELIST/namage/ rn_age_depth, rn_age_kill_rate 
46      !!----------------------------------------------------------------------
47      ! Variable setting
48      ctrcnm    (jp_age0) = 'Age'
49      ctrcln    (jp_age0) = 'Sea water age since surface contact'
50      ctrcun    (jp_age0) = 'year'
51      ln_trc_ini(jp_age0) = .false.
52      !                             ! Open namelist files
53      CALL ctl_opn( numnatg_ref, 'namelist_age_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
54      CALL ctl_opn( numnatg_cfg, 'namelist_age_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
55      IF(lwm) CALL ctl_opn( numong, 'output.namelist.age', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
56
57      REWIND( numnatg_ref )              ! Namelist namagedate in reference namelist : AGE parameters
58      READ  ( numnatg_ref, namage, IOSTAT = ios, ERR = 901)
59901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namage in reference namelist', lwp )
60
61      REWIND( numnatg_cfg )              ! Namelist namagedate in configuration namelist : AGE parameters
62      READ  ( numnatg_cfg, namage, IOSTAT = ios, ERR = 902 )
63902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namage in configuration namelist', lwp )
64      IF(lwm) WRITE ( numong, namage )
65
66      IF(lwp) THEN                  ! control print
67         WRITE(numout,*)
68         WRITE(numout,*) ' trc_nam_age: Read namage, namelist for Age passive tracer'
69         WRITE(numout,*) ' ~~~~~~~'
70         WRITE(numout,*) '  depth over which age tracer reset to zero                              rn_age_depth      = ', rn_age_depth 
71         WRITE(numout,*) '  recip of relax. timescale (s) for age tracer shallower than age_depth  rn_age_kill_rate  = ', rn_age_kill_rate 
72      ENDIF
73
74      IF(lwm) CALL FLUSH ( numong )     ! flush output namelist
75
76   END SUBROUTINE trc_nam_age
77   
78#else
79   !!----------------------------------------------------------------------
80   !!  Dummy module :                                                No AGE
81   !!----------------------------------------------------------------------
82CONTAINS
83   SUBROUTINE trc_nam_age                      ! Empty routine
84   END  SUBROUTINE  trc_nam_age
85#endif 
86
87   !!======================================================================
88END MODULE trcnam_age
Note: See TracBrowser for help on using the repository browser.