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

source: trunk/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 5385

Last change on this file since 5385 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

  • Property svn:keywords set to Id
File size: 5.8 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#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
[3294]18   USE iom             ! I/O manager
[2038]19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
24
25   !!----------------------------------------------------------------------
[2287]26   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[2281]27   !! $Id$
[2287]28   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]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
[3294]40      !!       values called at the first timestep (nittrc000)
[2038]41      !!
42      !! ** input   :   Namelist namcfc
43      !!----------------------------------------------------------------------
[4147]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
[2038]48      INTEGER :: jl, jn
[3294]49      TYPE(DIAG), DIMENSION(jp_cfc_2d) :: cfcdia2d
[2038]50      !!
51      NAMELIST/namcfcdate/ ndate_beg, nyear_res
[3294]52      NAMELIST/namcfcdia/  cfcdia2d     ! additional diagnostics
[4147]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. )
[4624]57      IF(lwm) CALL ctl_opn( numonc, 'output.namelist.cfc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
[2038]58
[4147]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 )
[2038]62
[4147]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 )
[4624]66      IF(lwm) WRITE ( numonc, namcfcdate )
[2038]67
68      IF(lwp) THEN                  ! control print
69         WRITE(numout,*)
70         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
71         WRITE(numout,*) ' ~~~~~~~'
72         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
73         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
74      ENDIF
75      nyear_beg = ndate_beg / 10000
76      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
77      !
78
[3294]79      IF( .NOT.lk_iomput .AND. ln_diatrc ) THEN
80         !
81         ! Namelist namcfcdia
82         ! -------------------
[4147]83         REWIND( numnatc_ref )              ! Namelist namcfcdia in reference namelist : CFC diagnostics
84         READ  ( numnatc_ref, namcfcdia, IOSTAT = ios, ERR = 903)
85903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdia in reference namelist', lwp )
[2038]86
[4147]87         REWIND( numnatc_cfg )              ! Namelist namcfcdia in configuration namelist : CFC diagnostics
88         READ  ( numnatc_cfg, namcfcdia, IOSTAT = ios, ERR = 904 )
89904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdia in configuration namelist', lwp )
[4624]90         IF(lwm) WRITE ( numonc, namcfcdia )
[2038]91
92         DO jl = 1, jp_cfc_2d
93            jn = jp_cfc0_2d + jl - 1
[3294]94            ctrc2d(jn) = TRIM( cfcdia2d(jl)%sname )
95            ctrc2l(jn) = TRIM( cfcdia2d(jl)%lname )
96            ctrc2u(jn) = TRIM( cfcdia2d(jl)%units )
97         END DO
98
99         IF(lwp) THEN                   ! control print
100            WRITE(numout,*)
101            WRITE(numout,*) ' Namelist : natadd'
102            DO jl = 1, jp_cfc_2d
103               jn = jp_cfc0_2d + jl - 1
104               WRITE(numout,*) '  2d diag nb : ', jn, '    short name : ', ctrc2d(jn), &
105                 &             '  long name  : ', ctrc2l(jn), '   unit : ', ctrc2u(jn)
106            END DO
[2038]107            WRITE(numout,*) ' '
[3294]108         ENDIF
109         !
[2038]110      ENDIF
111
[4624]112   IF(lwm) CALL FLUSH ( numonc )     ! flush output namelist CFC
[4147]113
[2038]114   END SUBROUTINE trc_nam_cfc
115   
116#else
117   !!----------------------------------------------------------------------
118   !!  Dummy module :                                                No CFC
119   !!----------------------------------------------------------------------
120CONTAINS
121   SUBROUTINE trc_nam_cfc                      ! Empty routine
122   END  SUBROUTINE  trc_nam_cfc
123#endif 
124
125   !!======================================================================
126END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.