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

source: branches/NERC/dev_r5518_GO6_COAREbulk/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 8657

Last change on this file since 8657 was 8657, checked in by jpalmier, 7 years ago

update the branch to match last GO6 changes

File size: 4.6 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
49      !!
50      NAMELIST/namcfcdate/ ndate_beg, nyear_res, simu_type 
51      !!----------------------------------------------------------------------
52      !                             ! Open namelist files
53      CALL ctl_opn( numnatc_ref, 'namelist_cfc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
54      CALL ctl_opn( numnatc_cfg, 'namelist_cfc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
55      IF(lwm) CALL ctl_opn( numonc, 'output.namelist.cfc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
56
57      REWIND( numnatc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters
58      READ  ( numnatc_ref, namcfcdate, IOSTAT = ios, ERR = 901)
59901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in reference namelist', lwp )
60
61      REWIND( numnatc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters
62      READ  ( numnatc_cfg, namcfcdate, IOSTAT = ios, ERR = 902 )
63902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in configuration namelist', lwp )
64      IF(lwm) WRITE ( numonc, namcfcdate )
65
66      IF(lwp) THEN                  ! control print
67         WRITE(numout,*)
68         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
69         WRITE(numout,*) ' ~~~~~~~'
70         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
71         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
72         IF (simu_type==1) THEN
73            WRITE(numout,*) ' CFC running on SPIN-UP mode             simu_type = ', simu_type
74         ELSEIF (simu_type==2) THEN
75            WRITE(numout,*) ' CFC running on HINDCAST/PROJECTION mode simu_type = ', simu_type
76         ENDIF
77      ENDIF
78      nyear_beg = ndate_beg / 10000
79      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
80      !
81
82   IF(lwm) CALL FLUSH ( numonc )     ! flush output namelist CFC
83
84   END SUBROUTINE trc_nam_cfc
85   
86#else
87   !!----------------------------------------------------------------------
88   !!  Dummy module :                                                No CFC
89   !!----------------------------------------------------------------------
90CONTAINS
91   SUBROUTINE trc_nam_cfc                      ! Empty routine
92   END  SUBROUTINE  trc_nam_cfc
93#endif 
94
95   !!======================================================================
96END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.