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.F90 in branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 4148

Last change on this file since 4148 was 4148, checked in by cetlod, 10 years ago

merge in trunk changes between r3853 and r3940 and commit the changes, see ticket #1169

  • Property svn:keywords set to Id
File size: 12.6 KB
Line 
1MODULE trcnam
2   !!======================================================================
3   !!                       ***  MODULE trcnam  ***
4   !! TOP :   Read and print options for the passive tracer run (namelist)
5   !!======================================================================
6   !! History :    -   !  1996-11  (M.A. Foujols, M. Levy)  original code
7   !!              -   !  1998-04  (M.A Foujols, L. Bopp) ahtrb0 for isopycnal mixing
8   !!              -   !  1999-10  (M.A. Foujols, M. Levy) separation of sms
9   !!              -   !  2000-07  (A. Estublier) add TVD and MUSCL : Tests on ndttrc
10   !!              -   !  2000-11  (M.A Foujols, E Kestenare) trcrat, ahtrc0 and aeivtr0
11   !!              -   !  2001-01 (E Kestenare) suppress ndttrc=1 for CEN2 and TVD schemes
12   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
13   !!----------------------------------------------------------------------
14#if defined key_top
15   !!----------------------------------------------------------------------
16   !!   'key_top'                                                TOP models
17   !!----------------------------------------------------------------------
18   !!   trc_nam    :  Read and print options for the passive tracer run (namelist)
19   !!----------------------------------------------------------------------
20   USE oce_trc           ! shared variables between ocean and passive tracers
21   USE trc               ! passive tracers common variables
22   USE trcnam_trp        ! Transport namelist
23   USE trcnam_pisces     ! PISCES namelist
24   USE trcnam_cfc        ! CFC SMS namelist
25   USE trcnam_c14b       ! C14 SMS namelist
26   USE trcnam_my_trc     ! MY_TRC SMS namelist
27   USE trdmod_oce       
28   USE trdmod_trc_oce
29   USE iom               ! I/O manager
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC trc_nam      ! called in trcini
35
36   !! * Substitutions
37#  include "top_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
40   !! $Id$
41   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE trc_nam
47      !!---------------------------------------------------------------------
48      !!                     ***  ROUTINE trc_nam  ***
49      !!
50      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
51      !!
52      !! ** Method  : - read passive tracer namelist
53      !!              - read namelist of each defined SMS model
54      !!                ( (PISCES, CFC, MY_TRC )
55      !!---------------------------------------------------------------------
56      INTEGER ::  jn, ierr
57      INTEGER ::  ios                 ! Local integer output status for namelist read
58      ! Definition of a tracer as a structure
59      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput
60      !!
61      NAMELIST/namtrc/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, &
62         &             cn_trcrst_in, cn_trcrst_out, sn_tracer, ln_trcdta, &
63         &             ln_trcdmp, ln_trcdmp_clo, ln_top_euler
64#if defined key_trdmld_trc  || defined key_trdtrc
65      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
66         &                ln_trdmld_trc_restart, ln_trdmld_trc_instant, &
67         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
68#endif
69      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio
70
71      !!---------------------------------------------------------------------
72
73      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
74      IF(lwp) WRITE(numout,*) '~~~~~~~'
75
76      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. )
77      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. )
78      CALL ctl_opn( numont    , 'output.namelist.top', 'REPLACE', 'FORMATTED', 'SEQUENTIAL',-1, numout, .FALSE. )
79
80      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
81      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
82901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
83
84      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
85      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
86902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
87      WRITE ( numont, namtrc )
88
89      DO jn = 1, jptra
90         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
91         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
92         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
93         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
94         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
95      END DO
96
97      !!KPE  computes the first time step of tracer model
98      nittrc000 = nit000 + nn_dttrc - 1
99 
100
101      IF(lwp) THEN                   ! control print
102         WRITE(numout,*)
103         WRITE(numout,*) ' Namelist : namtrc'
104         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
105         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
106         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
107         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
108         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
109         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
110         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
111         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
112         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
113         WRITE(numout,*) ' '
114         DO jn = 1, jptra
115            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
116         END DO
117         WRITE(numout,*) ' '
118      ENDIF
119
120      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step
121 
122      IF(lwp) THEN                   ! control print
123        WRITE(numout,*) 
124        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1)
125        WRITE(numout,*) 
126      ENDIF
127
128      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
129      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
130903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
131
132      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
133      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
134904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
135      WRITE ( numont, namtrc_dia )
136
137      IF(lwp) THEN
138         WRITE(numout,*)
139         WRITE(numout,*)
140         WRITE(numout,*) ' Namelist : namtrc_dia'
141         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
142         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
143         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
144         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
145         WRITE(numout,*) ' '
146      ENDIF
147
148      IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN
149         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
150           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
151           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
152         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
153         !
154         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
155         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
156         !
157      ENDIF
158
159      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN
160         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
161           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
162         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
163         !
164         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
165         !
166      ENDIF
167
168      ! namelist of transport
169      ! ---------------------
170      CALL trc_nam_trp
171
172
173      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data
174      !
175      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data
176      !
177      IF( .NOT.ln_trcdta ) THEN
178         ln_trc_ini(:) = .FALSE.
179      ENDIF
180
181      IF(lwp) THEN                   ! control print
182         IF( ln_rsttr ) THEN
183            WRITE(numout,*)
184            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
185            WRITE(numout,*)
186         ENDIF
187         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
188            WRITE(numout,*)
189            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies '
190            WRITE(numout,*)
191         ENDIF
192         IF( .NOT.ln_trcdta ) THEN
193            WRITE(numout,*)
194            WRITE(numout,*) '  All the passive tracers are initialised with constant values '
195            WRITE(numout,*)
196         ENDIF
197      ENDIF
198
199
200#if defined key_trdmld_trc || defined key_trdtrc
201
202         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
203         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
204905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
205
206         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
207         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
208906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
209         WRITE ( numont, namtrc_trd )
210
211         IF(lwp) THEN
212            WRITE(numout,*)
213            WRITE(numout,*) ' trd_mld_trc_init : read namelist namtrc_trd                    '
214            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
215            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
216            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
217            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmld_trc_restart  = ', ln_trdmld_trc_restart
218            WRITE(numout,*) '   * flag to diagnose trends of                                 '
219            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmld_trc_instant  = ', ln_trdmld_trc_instant
220            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
221            DO jn = 1, jptra
222               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
223            END DO
224         ENDIF
225#endif
226
227
228      ! namelist of SMS
229      ! ---------------     
230      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
231      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
232      ENDIF
233
234      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
235      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
236      ENDIF
237
238      IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers
239      ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used'
240      ENDIF
241
242      IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
243      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
244      ENDIF
245      !
246   END SUBROUTINE trc_nam
247
248#else
249   !!----------------------------------------------------------------------
250   !!  Dummy module :                                     No passive tracer
251   !!----------------------------------------------------------------------
252CONTAINS
253   SUBROUTINE trc_nam                      ! Empty routine   
254   END SUBROUTINE trc_nam
255#endif
256
257   !!----------------------------------------------------------------------
258   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
259   !! $Id$
260   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
261   !!======================================================================
262END MODULE  trcnam
Note: See TracBrowser for help on using the repository browser.