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_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 4290

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

fix to lwp use for namelist reads

  • Property svn:keywords set to Id
File size: 15.9 KB
RevLine 
[2038]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   !!----------------------------------------------------------------------
[3294]20   USE oce_trc           ! shared variables between ocean and passive tracers
21   USE trc               ! passive tracers common variables
[2038]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
[3294]27   USE trdmod_oce       
[2038]28   USE trdmod_trc_oce
[3294]29   USE iom               ! I/O manager
[2038]30
31   IMPLICIT NONE
32   PRIVATE
33
[4152]34   PUBLIC trc_nam_run  ! called in trcini
[2038]35   PUBLIC trc_nam      ! called in trcini
36
37   !! * Substitutions
38#  include "top_substitute.h90"
39   !!----------------------------------------------------------------------
[2287]40   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[2281]41   !! $Id$
[2287]42   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]43   !!----------------------------------------------------------------------
44
45CONTAINS
46
[4152]47
[2038]48   SUBROUTINE trc_nam
49      !!---------------------------------------------------------------------
50      !!                     ***  ROUTINE trc_nam  ***
51      !!
52      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
53      !!
54      !! ** Method  : - read passive tracer namelist
55      !!              - read namelist of each defined SMS model
[3680]56      !!                ( (PISCES, CFC, MY_TRC )
[2038]57      !!---------------------------------------------------------------------
[4154]58      INTEGER  ::   jn                  ! dummy loop indice
[4152]59      !                                        !   Parameters of the run
60      IF( .NOT. lk_offline ) CALL trc_nam_run
61     
62      !                                        !  passive tracer informations
63      CALL trc_nam_trc
64     
65      !                                        !   Parameters of additional diagnostics
66      CALL trc_nam_dia
[2038]67
[4152]68      !                                        !   namelist of transport
69      CALL trc_nam_trp
[2038]70
71
[4152]72      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data
73      !
74      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data
75      !
76      IF( .NOT.ln_trcdta ) THEN
77         ln_trc_ini(:) = .FALSE.
78      ENDIF
[2038]79
[4152]80     IF(lwp) THEN                   ! control print
[2038]81         WRITE(numout,*)
82         WRITE(numout,*) ' Namelist : namtrc'
[3319]83         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
84         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
[4148]85         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
[2038]86         WRITE(numout,*) ' '
87         DO jn = 1, jptra
[3294]88            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
[2038]89         END DO
[3294]90         WRITE(numout,*) ' '
[2038]91      ENDIF
92
[3294]93      IF(lwp) THEN                   ! control print
94         IF( ln_rsttr ) THEN
95            WRITE(numout,*)
[4148]96            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
[3294]97            WRITE(numout,*)
98         ENDIF
[4148]99         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
100            WRITE(numout,*)
101            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies '
102            WRITE(numout,*)
103         ENDIF
104         IF( .NOT.ln_trcdta ) THEN
105            WRITE(numout,*)
106            WRITE(numout,*) '  All the passive tracers are initialised with constant values '
107            WRITE(numout,*)
108         ENDIF
[3294]109      ENDIF
110
[4152]111     
112      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step
113 
114      IF(lwp) THEN                   ! control print
115        WRITE(numout,*) 
116        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1)
117        WRITE(numout,*) 
118      ENDIF
[3294]119
[4152]120
[3294]121#if defined key_trdmld_trc || defined key_trdtrc
122
[4147]123         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
124         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
125905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
[3294]126
[4147]127         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
128         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
129906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
130         WRITE ( numont, namtrc_trd )
131
[3294]132         IF(lwp) THEN
133            WRITE(numout,*)
134            WRITE(numout,*) ' trd_mld_trc_init : read namelist namtrc_trd                    '
135            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
136            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
137            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
138            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmld_trc_restart  = ', ln_trdmld_trc_restart
139            WRITE(numout,*) '   * flag to diagnose trends of                                 '
140            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmld_trc_instant  = ', ln_trdmld_trc_instant
141            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
142            DO jn = 1, jptra
143               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
144            END DO
145         ENDIF
146#endif
147
148
[2038]149      ! namelist of SMS
150      ! ---------------     
151      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
152      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
153      ENDIF
154
155      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
156      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
157      ENDIF
158
159      IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers
160      ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used'
161      ENDIF
162
163      IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
164      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
165      ENDIF
166      !
167   END SUBROUTINE trc_nam
168
[4152]169   SUBROUTINE trc_nam_run
170      !!---------------------------------------------------------------------
171      !!                     ***  ROUTINE trc_nam  ***
172      !!
173      !! ** Purpose :   read options for the passive tracer run (namelist)
174      !!
175      !!---------------------------------------------------------------------
176      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, &
177        &                  cn_trcrst_in, cn_trcrst_out
178
[4154]179      INTEGER  ::   ios                 ! Local integer output status for namelist read
180
[4152]181      !!---------------------------------------------------------------------
182
183
184      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
185      IF(lwp) WRITE(numout,*) '~~~~~~~'
186
[4290]187      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
188      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
189      CALL ctl_opn( numont    , 'output.namelist.top', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea )
[4152]190
191      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
192      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
193901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
194
195      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
196      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
197902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
[4154]198      WRITE ( numont, namtrc_run )
[4152]199
200      !  computes the first time step of tracer model
201      nittrc000 = nit000 + nn_dttrc - 1
202
203      IF(lwp) THEN                   ! control print
204         WRITE(numout,*)
[4159]205         WRITE(numout,*) ' Namelist : namtrc_run'
[4152]206         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
207         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
208         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
209         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
[4159]210         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
211         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
[4152]212         WRITE(numout,*) ' '
213      ENDIF
214      !
215    END SUBROUTINE trc_nam_run
216
217
218   SUBROUTINE trc_nam_trc
219      !!---------------------------------------------------------------------
220      !!                     ***  ROUTINE trc_nam  ***
221      !!
222      !! ** Purpose :   read options for the passive tracer run (namelist)
223      !!
224      !!---------------------------------------------------------------------
225      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput
226      !!
227      NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo
[4154]228 
229      INTEGER  ::   ios                 ! Local integer output status for namelist read
230      INTEGER  ::   jn                  ! dummy loop indice
[4152]231      !!---------------------------------------------------------------------
232      IF(lwp) WRITE(numout,*)
233      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
234      IF(lwp) WRITE(numout,*) '~~~~~~~'
235
236
237      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
238      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
239901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
240
241      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
242      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
243902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
244      WRITE ( numont, namtrc )
245
246      DO jn = 1, jptra
247         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
248         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
249         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
250         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
251         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
252      END DO
253     
254    END SUBROUTINE trc_nam_trc
255
256
257   SUBROUTINE trc_nam_dia
258      !!---------------------------------------------------------------------
259      !!                     ***  ROUTINE trc_nam_dia  ***
260      !!
261      !! ** Purpose :   read options for the passive tracer diagnostics
262      !!
263      !! ** Method  : - read passive tracer namelist
264      !!              - read namelist of each defined SMS model
265      !!                ( (PISCES, CFC, MY_TRC )
266      !!---------------------------------------------------------------------
267      INTEGER ::  ierr
268#if defined key_trdmld_trc  || defined key_trdtrc
269      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
270         &                ln_trdmld_trc_restart, ln_trdmld_trc_instant, &
271         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
272#endif
273      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio
274
[4154]275      INTEGER  ::   ios                 ! Local integer output status for namelist read
[4152]276      !!---------------------------------------------------------------------
277
278      IF(lwp) WRITE(numout,*) 
279      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
280      IF(lwp) WRITE(numout,*) '~~~~~~~'
281
282      IF(lwp) WRITE(numout,*)
283      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
284      IF(lwp) WRITE(numout,*) '~~~~~~~'
285
286      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
287      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
288903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
289
290      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
291      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
292904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
293      WRITE ( numont, namtrc_dia )
294
295      IF(lwp) THEN
296         WRITE(numout,*)
297         WRITE(numout,*)
298         WRITE(numout,*) ' Namelist : namtrc_dia'
299         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
300         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
301         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
302         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
303         WRITE(numout,*) ' '
304      ENDIF
305
306      IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN
307         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
308           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
309           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
310         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
311         !
312         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
313         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
314         !
315      ENDIF
316
317      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN
318         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
319           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
320         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
321         !
322         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
323         !
324      ENDIF
325      !
326   END SUBROUTINE trc_nam_dia
327
[2038]328#else
329   !!----------------------------------------------------------------------
330   !!  Dummy module :                                     No passive tracer
331   !!----------------------------------------------------------------------
332CONTAINS
333   SUBROUTINE trc_nam                      ! Empty routine   
334   END SUBROUTINE trc_nam
[4152]335   SUBROUTINE trc_nam_run                      ! Empty routine   
336   END SUBROUTINE trc_nam_run
[2038]337#endif
338
[2104]339   !!----------------------------------------------------------------------
[2287]340   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[2281]341   !! $Id$
[2287]342   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]343   !!======================================================================
344END MODULE  trcnam
Note: See TracBrowser for help on using the repository browser.