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

source: branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90 @ 2830

Last change on this file since 2830 was 2830, checked in by kpedwards, 13 years ago

Updates to average physics variables for TOP substepping.

  • Property svn:keywords set to Id
File size: 5.2 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
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module
23
24   !!----------------------------------------------------------------------
25   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
26   !! $Id$
27   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
28   !!----------------------------------------------------------------------
29
30CONTAINS
31
32   SUBROUTINE trc_nam_cfc
33      !!-------------------------------------------------------------------
34      !!                  ***  ROUTINE trc_nam_cfc  ***
35      !!                 
36      !! ** Purpose :   Definition some run parameter for CFC model
37      !!
38      !! ** Method  :   Read the namcfc namelist and check the parameter
39      !!       values called at the first timestep (nittrc000)
40      !!
41      !! ** input   :   Namelist namcfc
42      !!----------------------------------------------------------------------
43      INTEGER ::   numnatc
44#if defined key_diatrc && ! defined key_iomput
45      ! definition of additional diagnostic as a structure
46      INTEGER :: jl, jn
47      TYPE DIAG
48         CHARACTER(len = 20)  :: snamedia   !: short name
49         CHARACTER(len = 80 ) :: lnamedia   !: long name
50         CHARACTER(len = 20 ) :: unitdia    !: unit
51      END TYPE DIAG
52
53      TYPE(DIAG) , DIMENSION(jp_cfc_2d) :: cfcdia2d
54#endif
55      !!
56      NAMELIST/namcfcdate/ ndate_beg, nyear_res
57#if defined key_diatrc && ! defined key_iomput
58      NAMELIST/namcfcdia/nn_writedia, cfcdia2d     ! additional diagnostics
59#endif
60      !!-------------------------------------------------------------------
61
62      ndate_beg = 300101            ! default namelist value
63      nyear_res = 1950
64
65      !                             ! Open namelist file
66      CALL ctl_opn( numnatc, 'namelist_cfc', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
67         
68      READ( numnatc , namcfcdate )     ! read namelist
69
70      IF(lwp) THEN                  ! control print
71         WRITE(numout,*)
72         WRITE(numout,*) ' trc_nam: Read namdates, namelist for CFC chemical model'
73         WRITE(numout,*) ' ~~~~~~~'
74         WRITE(numout,*) '    initial calendar date (aammjj) for CFC  ndate_beg = ', ndate_beg
75         WRITE(numout,*) '    restoring time constant (year)          nyear_res = ', nyear_res
76      ENDIF
77      nyear_beg = ndate_beg / 10000
78      IF(lwp) WRITE(numout,*) '    initial year (aa)                       nyear_beg = ', nyear_beg
79      !
80#if defined key_diatrc && ! defined key_iomput
81
82      ! Namelist namcfcdia
83      ! -------------------
84      nn_writedia = 10                   ! default values
85
86      DO jl = 1, jp_cfc_2d
87         jn = jp_cfc0_2d + jl - 1 
88         WRITE(ctrc2d(jn),'("2D_",I1)') jn                      ! short name
89         WRITE(ctrc2l(jn),'("2D DIAGNOSTIC NUMBER ",I2)') jn    ! long name
90         ctrc2u(jn) = ' '                                       ! units
91      END DO
92
93      REWIND( numnatc )               ! read natrtd
94      READ  ( numnatc, namcfcdia )
95
96      DO jl = 1, jp_cfc_2d
97         jn = jp_cfc0_2d + jl - 1
98         ctrc2d(jn) = cfcdia2d(jl)%snamedia
99         ctrc2l(jn) = cfcdia2d(jl)%lnamedia
100         ctrc2u(jn) = cfcdia2d(jl)%unitdia
101      END DO
102
103
104      IF(lwp) THEN                   ! control print
105         WRITE(numout,*)
106         WRITE(numout,*) ' Namelist : natadd'
107         WRITE(numout,*) '    frequency of outputs for additional arrays nn_writedia = ', nn_writedia
108         DO jl = 1, jp_cfc_2d
109            jn = jp_cfc0_2d + jl - 1
110            WRITE(numout,*) '   2d output field No : ',jn
111            WRITE(numout,*) '   short name         : ', TRIM(ctrc2d(jn))
112            WRITE(numout,*) '   long name          : ', TRIM(ctrc2l(jn))
113            WRITE(numout,*) '   unit               : ', TRIM(ctrc2u(jn))
114            WRITE(numout,*) ' '
115         END DO
116      ENDIF
117#endif
118
119   END SUBROUTINE trc_nam_cfc
120   
121#else
122   !!----------------------------------------------------------------------
123   !!  Dummy module :                                                No CFC
124   !!----------------------------------------------------------------------
125CONTAINS
126   SUBROUTINE trc_nam_cfc                      ! Empty routine
127   END  SUBROUTINE  trc_nam_cfc
128#endif 
129
130   !!======================================================================
131END MODULE trcnam_cfc
Note: See TracBrowser for help on using the repository browser.