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 @ 3294

Last change on this file since 3294 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

  • Property svn:keywords set to Id
File size: 4.7 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
45      INTEGER :: jl, jn
46      TYPE(DIAG), DIMENSION(jp_cfc_2d) :: cfcdia2d
47      !!
48      NAMELIST/namcfcdate/ ndate_beg, nyear_res
49      NAMELIST/namcfcdia/  cfcdia2d     ! additional diagnostics
50      !!-------------------------------------------------------------------
51
52      ndate_beg = 300101            ! default namelist value
53      nyear_res = 1950
54
55      !                             ! Open namelist file
56      CALL ctl_opn( numnatc, 'namelist_cfc', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
57         
58      READ( numnatc , namcfcdate )     ! read namelist
59
60      IF(lwp) THEN                  ! control print
61         WRITE(numout,*)
62         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
63         WRITE(numout,*) ' ~~~~~~~'
64         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
65         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
66      ENDIF
67      nyear_beg = ndate_beg / 10000
68      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
69      !
70
71      IF( .NOT.lk_iomput .AND. ln_diatrc ) THEN
72         !
73         ! Namelist namcfcdia
74         ! -------------------
75         DO jl = 1, jp_cfc_2d
76            WRITE(cfcdia2d(jl)%sname,'("2D_",I1)') jl                      ! short name
77            WRITE(cfcdia2d(jl)%lname,'("2D DIAGNOSTIC NUMBER ",I2)') jl    ! long name
78            cfcdia2d(jl)%units = ' '                                       ! units
79         END DO
80
81         REWIND( numnatc )               ! read natrtd
82         READ  ( numnatc, namcfcdia )
83
84         DO jl = 1, jp_cfc_2d
85            jn = jp_cfc0_2d + jl - 1
86            ctrc2d(jn) = TRIM( cfcdia2d(jl)%sname )
87            ctrc2l(jn) = TRIM( cfcdia2d(jl)%lname )
88            ctrc2u(jn) = TRIM( cfcdia2d(jl)%units )
89         END DO
90
91         IF(lwp) THEN                   ! control print
92            WRITE(numout,*)
93            WRITE(numout,*) ' Namelist : natadd'
94            DO jl = 1, jp_cfc_2d
95               jn = jp_cfc0_2d + jl - 1
96               WRITE(numout,*) '  2d diag nb : ', jn, '    short name : ', ctrc2d(jn), &
97                 &             '  long name  : ', ctrc2l(jn), '   unit : ', ctrc2u(jn)
98            END DO
99            WRITE(numout,*) ' '
100         ENDIF
101         !
102      ENDIF
103
104   END SUBROUTINE trc_nam_cfc
105   
106#else
107   !!----------------------------------------------------------------------
108   !!  Dummy module :                                                No CFC
109   !!----------------------------------------------------------------------
110CONTAINS
111   SUBROUTINE trc_nam_cfc                      ! Empty routine
112   END  SUBROUTINE  trc_nam_cfc
113#endif 
114
115   !!======================================================================
116END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.