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

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 5.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   USE yomhook, ONLY: lhook, dr_hook
21   USE parkind1, ONLY: jprb, jpim
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
27
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE trc_nam_cfc
37      !!-------------------------------------------------------------------
38      !!                  ***  ROUTINE trc_nam_cfc  ***
39      !!                 
40      !! ** Purpose :   Definition some run parameter for CFC model
41      !!
42      !! ** Method  :   Read the namcfc namelist and check the parameter
43      !!       values called at the first timestep (nittrc000)
44      !!
45      !! ** input   :   Namelist namcfc
46      !!----------------------------------------------------------------------
47      INTEGER ::  numnatc_ref = -1   ! Logical unit for reference CFC namelist
48      INTEGER ::  numnatc_cfg = -1   ! Logical unit for configuration CFC namelist
49      INTEGER ::  numonc      = -1   ! Logical unit for output namelist
50      INTEGER :: ios                 ! Local integer output status for namelist read
51      INTEGER :: jl, jn
52      !!
53      NAMELIST/namcfcdate/ ndate_beg, nyear_res, simu_type 
54      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
55      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
56      REAL(KIND=jprb)               :: zhook_handle
57
58      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_NAM_CFC'
59
60      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
61
62      !!----------------------------------------------------------------------
63      !                             ! Open namelist files
64      CALL ctl_opn( numnatc_ref, 'namelist_cfc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
65      CALL ctl_opn( numnatc_cfg, 'namelist_cfc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
66      IF(lwm) CALL ctl_opn( numonc, 'output.namelist.cfc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
67
68      REWIND( numnatc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters
69      READ  ( numnatc_ref, namcfcdate, IOSTAT = ios, ERR = 901)
70901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in reference namelist', lwp )
71
72      REWIND( numnatc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters
73      READ  ( numnatc_cfg, namcfcdate, IOSTAT = ios, ERR = 902 )
74902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfcdate in configuration namelist', lwp )
75      IF(lwm) WRITE ( numonc, namcfcdate )
76
77      IF(lwp) THEN                  ! control print
78         WRITE(numout,*)
79         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
80         WRITE(numout,*) ' ~~~~~~~'
81         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
82         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
83         IF (simu_type==1) THEN
84            WRITE(numout,*) ' CFC running on SPIN-UP mode             simu_type = ', simu_type
85         ELSEIF (simu_type==2) THEN
86            WRITE(numout,*) ' CFC running on HINDCAST/PROJECTION mode simu_type = ', simu_type
87         ENDIF
88      ENDIF
89      nyear_beg = ndate_beg / 10000
90      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
91      !
92
93   IF(lwm) CALL FLUSH ( numonc )     ! flush output namelist CFC
94
95      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
96   END SUBROUTINE trc_nam_cfc
97   
98#else
99   !!----------------------------------------------------------------------
100   !!  Dummy module :                                                No CFC
101   !!----------------------------------------------------------------------
102CONTAINS
103   SUBROUTINE trc_nam_cfc                      ! Empty routine
104   INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
105   INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
106   REAL(KIND=jprb)               :: zhook_handle
107
108   CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_NAM_CFC'
109
110   IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
111
112   IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
113   END  SUBROUTINE  trc_nam_cfc
114#endif 
115
116   !!======================================================================
117END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.