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/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 8353

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

3.6 stable: update TOP modules and shared configuraton files for CMIP6 (#1925)

  • Property svn:keywords set to Id
File size: 7.4 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#if defined key_cfc
9   !!----------------------------------------------------------------------
10   !!   'key_cfc'                                               CFC tracers
11   !!----------------------------------------------------------------------
12   !! trc_nam_cfc      : CFC model initialisation
13   !!----------------------------------------------------------------------
14   USE oce_trc         ! Ocean variables
15   USE par_trc         ! TOP parameters
16   USE trc             ! TOP variables
17   USE trcsms_cfc      ! CFC specific variable
18   USE iom             ! I/O manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
24
25   !!----------------------------------------------------------------------
26   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
27   !! $Id$
28   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
29   !!----------------------------------------------------------------------
30
31CONTAINS
32
33   SUBROUTINE trc_nam_cfc
34      !!-------------------------------------------------------------------
35      !!                  ***  ROUTINE trc_nam_cfc  ***
36      !!                 
37      !! ** Purpose :   Definition some run parameter for CFC model
38      !!
39      !! ** Method  :   Read the namcfc namelist and check the parameter
40      !!       values called at the first timestep (nittrc000)
41      !!
42      !! ** input   :   Namelist namcfc
43      !!----------------------------------------------------------------------
44      INTEGER ::  numnatc_ref = -1   ! Logical unit for reference CFC namelist
45      INTEGER ::  numnatc_cfg = -1   ! Logical unit for configuration CFC namelist
46      INTEGER ::  numonc      = -1   ! Logical unit for output namelist
47      INTEGER :: ios                 ! Local integer output status for namelist read
48      INTEGER :: jl, jn, cnt
49      TYPE(DIAG), DIMENSION(jp_cfc_2d) :: cfcdia2d
50      !!
51      NAMELIST/namcfcdate/ ndate_beg, nyear_res, clnamecfc
52      NAMELIST/namcfcdia/  cfcdia2d     ! additional diagnostics
53      !!----------------------------------------------------------------------
54      !                             ! Open namelist files
55      CALL ctl_opn( numnatc_ref, 'namelist_cfc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
56      CALL ctl_opn( numnatc_cfg, 'namelist_cfc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
57      IF(lwm) CALL ctl_opn( numonc, 'output.namelist.cfc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
58
59      REWIND( numnatc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters
60      READ  ( numnatc_ref, namcfcdate, IOSTAT = ios, ERR = 901)
61901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in reference namelist', lwp )
62
63      REWIND( numnatc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters
64      READ  ( numnatc_cfg, namcfcdate, IOSTAT = ios, ERR = 902 )
65902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in configuration namelist', lwp )
66      IF(lwm) WRITE ( numonc, namcfcdate )
67
68      jn = jp_cfc0 - 1
69      ! Variables setting
70      IF( lp_cfc11 ) THEN
71         jn = jn + 1
72         ctrcnm    (jn) = 'CFC11'
73         ctrcln    (jn) = 'Chlorofluoro carbon 11 Concentration'
74         ctrcun    (jn) = 'umolC/L'
75         ln_trc_ini(jn) = .false.
76         ln_trc_wri(jn) = .true.
77      ENDIF
78      !
79      IF( lp_cfc12 ) THEN
80         jn = jn + 1
81         ctrcnm    (jn) = 'CFC12'
82         ctrcln    (jn) = 'Chlorofluoro carbon 12 Concentration'
83         ctrcun    (jn) = 'umolC/L'
84         ln_trc_ini(jn) = .false.
85         ln_trc_wri(jn) = .true.
86      ENDIF
87      !
88      IF( lp_sf6 ) THEN
89         jn = jn + 1
90         ctrcnm    (jn) = 'SF6'
91         ctrcln    (jn) = 'Sulfur hexafluoride Concentration'
92         ctrcun    (jn) = 'umol/L'
93         ln_trc_ini(jn) = .false.
94         ln_trc_wri(jn) = .true.
95      ENDIF
96
97      IF(lwp) THEN                  ! control print
98         WRITE(numout,*) ' '
99         WRITE(numout,*) ' CFCs'
100         WRITE(numout,*) ' '
101         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
102         WRITE(numout,*) ' ~~~~~~~'
103         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
104         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
105         WRITE(numout,*) '    Atmospheric CFC concentrations file     clnamecfc = ', TRIM(clnamecfc)
106         WRITE(numout,*) '    Compute dynamics for CFC-11             lp_cfc11  = ', lp_cfc11
107         WRITE(numout,*) '    Compute dynamics for CFC-12             lp_cfc12  = ', lp_cfc12
108         WRITE(numout,*) '    Compute dynamics for SF6                lp_sf6    = ', lp_sf6
109      ENDIF
110      nyear_beg = ndate_beg / 10000
111      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
112      !
113      ! check consistency between CFC namelist and par_cfc setting
114      if ( jn - jp_cfc0 + 1 .ne. jp_cfc )  &
115      CALL ctl_stop( 'trc_nam_cfc: Number of selected CFCs is different from total CFC number (jp_cfc) specified in par_cfc.F90' )
116      !
117
118      IF( .NOT.lk_iomput .AND. ln_diatrc ) THEN
119         !
120         ! Namelist namcfcdia
121         ! -------------------
122         REWIND( numnatc_ref )              ! Namelist namcfcdia in reference namelist : CFC diagnostics
123         READ  ( numnatc_ref, namcfcdia, IOSTAT = ios, ERR = 903)
124903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdia in reference namelist', lwp )
125
126         REWIND( numnatc_cfg )              ! Namelist namcfcdia in configuration namelist : CFC diagnostics
127         READ  ( numnatc_cfg, namcfcdia, IOSTAT = ios, ERR = 904 )
128904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdia in configuration namelist', lwp )
129         IF(lwm) WRITE ( numonc, namcfcdia )
130
131         DO jl = 1, jp_cfc_2d
132            jn = jp_cfc0_2d + jl - 1
133            ctrc2d(jn) = TRIM( cfcdia2d(jl)%sname )
134            ctrc2l(jn) = TRIM( cfcdia2d(jl)%lname )
135            ctrc2u(jn) = TRIM( cfcdia2d(jl)%units )
136         END DO
137
138         IF(lwp) THEN                   ! control print
139            WRITE(numout,*)
140            WRITE(numout,*) ' Namelist : natadd'
141            DO jl = 1, jp_cfc_2d
142               jn = jp_cfc0_2d + jl - 1
143               WRITE(numout,*) '  2d diag nb : ', jn, '    short name : ', ctrc2d(jn), &
144                 &             '  long name  : ', ctrc2l(jn), '   unit : ', ctrc2u(jn)
145            END DO
146            WRITE(numout,*) ' '
147         ENDIF
148         !
149      ENDIF
150
151   IF(lwm) CALL FLUSH ( numonc )     ! flush output namelist CFC
152
153   END SUBROUTINE trc_nam_cfc
154   
155#else
156   !!----------------------------------------------------------------------
157   !!  Dummy module :                                                No CFC
158   !!----------------------------------------------------------------------
159CONTAINS
160   SUBROUTINE trc_nam_cfc                      ! Empty routine
161   END  SUBROUTINE  trc_nam_cfc
162#endif 
163
164   !!======================================================================
165END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.