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_cfc.F90 in NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/CFC – NEMO

source: NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/CFC/trcnam_cfc.F90 @ 10372

Last change on this file since 10372 was 10068, checked in by nicolasmartin, 6 years ago

First part of modifications to have a common default header : fix typos and SVN keywords properties

  • Property svn:keywords set to Id
File size: 4.3 KB
Line 
1MODULE trcnam_cfc
2   !!======================================================================
3   !!                         ***  MODULE trcnam_cfc  ***
4   !! TOP :   initialisation of some run parameters for CFC chemical model
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) from trcnam.cfc.h90
7   !!----------------------------------------------------------------------
8   !! trc_nam_cfc      : CFC model initialisation
9   !!----------------------------------------------------------------------
10   USE oce_trc         ! Ocean variables
11   USE trc             ! TOP variables
12   USE trcsms_cfc      ! CFC specific variable
13
14   IMPLICIT NONE
15   PRIVATE
16
17   CHARACTER(len=34), PUBLIC ::   clname ! Input filename of CFCs atm. concentrations
18
19   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
20
21   !!----------------------------------------------------------------------
22   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
23   !! $Id$
24   !! Software governed by the CeCILL license (see ./LICENSE)
25   !!----------------------------------------------------------------------
26CONTAINS
27
28   SUBROUTINE trc_nam_cfc
29      !!-------------------------------------------------------------------
30      !!                  ***  ROUTINE trc_nam_cfc  ***
31      !!                 
32      !! ** Purpose :   Definition some run parameter for CFC model
33      !!
34      !! ** Method  :   Read the namcfc namelist and check the parameter
35      !!       values called at the first timestep (nittrc000)
36      !!
37      !! ** input   :   Namelist namcfc
38      !!----------------------------------------------------------------------
39      INTEGER ::   ios   ! Local integer
40      INTEGER ::   jl, jn
41      !!
42      NAMELIST/namcfc/ ndate_beg, nyear_res, clname
43      !!----------------------------------------------------------------------
44      !
45      IF(lwp) THEN
46         WRITE(numout,*) ' '
47         WRITE(numout,*) ' CFCs'
48         WRITE(numout,*) ' '
49         WRITE(numout,*) ' trc_nam_cfc : Read namcfc namelist for CFC chemical model'
50         WRITE(numout,*) ' ~~~~~~~~~~~'
51      ENDIF
52      !
53      REWIND( numtrc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters
54      READ  ( numtrc_ref, namcfc, IOSTAT = ios, ERR = 901)
55901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfc in reference namelist', lwp )
56      REWIND( numtrc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters
57      READ  ( numtrc_cfg, namcfc, IOSTAT = ios, ERR = 902 )
58902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfc in configuration namelist', lwp )
59      IF(lwm) WRITE( numonr, namcfc )
60      IF(lwm) CALL FLUSH ( numonr )     ! flush output namelist CFC
61
62      IF(lwp) THEN                  ! control print
63         WRITE(numout,*) '   Namelist : namcfc'
64         WRITE(numout,*) '      initial calendar date (aammjj) for CFC     ndate_beg = ', ndate_beg, '[yymmdd]'
65         WRITE(numout,*) '      restoring time constant (year)             nyear_res = ', nyear_res
66      ENDIF
67      nyear_beg = ndate_beg / 10000
68      IF(lwp) WRITE(numout,*) '      associated initial year (aa)               nyear_beg = ', nyear_beg, '[yy]'
69      !
70      jn = jp_cfc0 - 1
71      ! Variables setting
72      IF( ln_cfc11 ) THEN
73         jn = jn + 1
74         ctrcnm    (jn) = 'CFC11'
75         ctrcln    (jn) = 'Chlorofluoro carbon 11 Concentration'
76         ctrcun    (jn) = 'umolC/L'
77         ln_trc_ini(jn) = .false.
78         ln_trc_sbc(jn) = .false.
79         ln_trc_cbc(jn) = .false.
80         ln_trc_obc(jn) = .false.
81      ENDIF
82      !
83      IF( ln_cfc12 ) THEN
84         jn = jn + 1
85         ctrcnm    (jn) = 'CFC12'
86         ctrcln    (jn) = 'Chlorofluoro carbon 12 Concentration'
87         ctrcun    (jn) = 'umolC/L'
88         ln_trc_ini(jn) = .false.
89         ln_trc_sbc(jn) = .false.
90         ln_trc_cbc(jn) = .false.
91         ln_trc_obc(jn) = .false.
92      ENDIF
93      !
94      IF( ln_sf6 ) THEN
95         jn = jn + 1
96         ctrcnm    (jn) = 'SF6'
97         ctrcln    (jn) = 'Sulfur hexafluoride Concentration'
98         ctrcun    (jn) = 'umol/L'
99         ln_trc_ini(jn) = .false.
100         ln_trc_sbc(jn) = .false.
101         ln_trc_cbc(jn) = .false.
102         ln_trc_obc(jn) = .false.
103      ENDIF
104      !
105   END SUBROUTINE trc_nam_cfc
106   
107   !!======================================================================
108END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.