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 branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 7211

Last change on this file since 7211 was 7211, checked in by lovato, 7 years ago

New top interface : Revisited CFC module with formulations from Wanninkhof (2014) + SF6 tracer

  • Property svn:keywords set to Id
File size: 4.2 KB
RevLine 
[2038]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
[7211]17   CHARACTER(len=34), PUBLIC ::   clname ! Input filename of CFCs atm. concentrations
18
[2038]19   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
20
21   !!----------------------------------------------------------------------
[2287]22   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[2281]23   !! $Id$
[2287]24   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]25   !!----------------------------------------------------------------------
26
27CONTAINS
28
29   SUBROUTINE trc_nam_cfc
30      !!-------------------------------------------------------------------
31      !!                  ***  ROUTINE trc_nam_cfc  ***
32      !!                 
33      !! ** Purpose :   Definition some run parameter for CFC model
34      !!
35      !! ** Method  :   Read the namcfc namelist and check the parameter
[3294]36      !!       values called at the first timestep (nittrc000)
[2038]37      !!
38      !! ** input   :   Namelist namcfc
39      !!----------------------------------------------------------------------
[4147]40      INTEGER :: ios                 ! Local integer output status for namelist read
[2038]41      INTEGER :: jl, jn
42      !!
[7211]43      NAMELIST/namcfc/ ndate_beg, nyear_res, clname
[4147]44      !!----------------------------------------------------------------------
[7211]45      !
46      jn = jp_cfc0 - 1
[7124]47      ! Variables setting
[7068]48      IF( ln_cfc11 ) THEN
[7211]49         jn = jn + 1
50         ctrcnm    (jn) = 'CFC11'
51         ctrcln    (jn) = 'Chlorofluoro carbon 11 Concentration'
52         ctrcun    (jn) = 'umolC/L'
53         ln_trc_ini(jn) = .false.
54         ln_trc_sbc(jn) = .false.
55         ln_trc_cbc(jn) = .false.
56         ln_trc_obc(jn) = .false.
[7068]57      ENDIF
58      !
59      IF( ln_cfc12 ) THEN
[7211]60         jn = jn + 1
61         ctrcnm    (jn) = 'CFC12'
62         ctrcln    (jn) = 'Chlorofluoro carbon 12 Concentration'
63         ctrcun    (jn) = 'umolC/L'
64         ln_trc_ini(jn) = .false.
65         ln_trc_sbc(jn) = .false.
66         ln_trc_cbc(jn) = .false.
67         ln_trc_obc(jn) = .false.
[7068]68      ENDIF
69      !
[7211]70      IF( ln_sf6 ) THEN
71         jn = jn + 1
72         ctrcnm    (jn) = 'SF6'
73         ctrcln    (jn) = 'Sulfur hexafluoride Concentration'
74         ctrcun    (jn) = 'umol/L'
75         ln_trc_ini(jn) = .false.
76         ln_trc_sbc(jn) = .false.
77         ln_trc_cbc(jn) = .false.
78         ln_trc_obc(jn) = .false.
79      ENDIF
80      !
[7041]81      REWIND( numtrc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters
82      READ  ( numtrc_ref, namcfc, IOSTAT = ios, ERR = 901)
83901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfc in reference namelist', lwp )
[2038]84
[7041]85      REWIND( numtrc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters
86      READ  ( numtrc_cfg, namcfc, IOSTAT = ios, ERR = 902 )
87902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfc in configuration namelist', lwp )
88      IF(lwm) WRITE ( numonr, namcfc )
[2038]89
90      IF(lwp) THEN                  ! control print
[7068]91         WRITE(numout,*) ' '
92         WRITE(numout,*) ' CFCs'
93         WRITE(numout,*) ' '
[2038]94         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
95         WRITE(numout,*) ' ~~~~~~~'
96         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
97         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
98      ENDIF
99      nyear_beg = ndate_beg / 10000
100      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
101      !
[7041]102      IF(lwm) CALL FLUSH ( numonr )     ! flush output namelist CFC
[2038]103
104   END SUBROUTINE trc_nam_cfc
105   
106   !!======================================================================
107END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.