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

source: trunk/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 6140

Last change on this file since 6140 was 6140, checked in by timgraham, 8 years ago

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

  • Property svn:keywords set to Id
File size: 18.0 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_pisces     ! PISCES namelist
23   USE trcnam_cfc        ! CFC SMS namelist
24   USE trcnam_c14b       ! C14 SMS namelist
25   USE trcnam_my_trc     ! MY_TRC SMS namelist
26   USE trd_oce       
27   USE trdtrc_oce
28   USE iom               ! I/O manager
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC trc_nam_run  ! called in trcini
34   PUBLIC trc_nam      ! called in trcini
35
36   !!----------------------------------------------------------------------
37   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
38   !! $Id$
39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE trc_nam
44      !!---------------------------------------------------------------------
45      !!                     ***  ROUTINE trc_nam  ***
46      !!
47      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
48      !!
49      !! ** Method  : - read passive tracer namelist
50      !!              - read namelist of each defined SMS model
51      !!                ( (PISCES, CFC, MY_TRC )
52      !!---------------------------------------------------------------------
53      INTEGER  ::   jn                  ! dummy loop indice
54      !                                 
55      IF( .NOT.lk_offline )   CALL trc_nam_run     ! Parameters of the run
56      !               
57                              CALL trc_nam_trc     ! passive tracer informations
58      !                                       
59                              CALL trc_nam_dia     ! Parameters of additional diagnostics
60      !                                     
61      !
62      IF( ln_rsttr                     )   ln_trcdta     = .FALSE.   ! restart : no need of clim data
63      !
64      IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta     = .TRUE.   ! damping : need to have clim data
65      !
66      IF( .NOT.ln_trcdta               )   ln_trc_ini(:) = .FALSE.
67
68      IF(lwp) THEN                   ! control print
69         WRITE(numout,*)
70         WRITE(numout,*) ' Namelist : namtrc'
71         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
72         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
73         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
74         WRITE(numout,*) ' '
75         DO jn = 1, jptra
76            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
77         END DO
78         WRITE(numout,*) ' '
79      ENDIF
80
81      IF(lwp) THEN                   ! control print
82         IF( ln_rsttr ) THEN
83            WRITE(numout,*)
84            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
85            WRITE(numout,*)
86         ENDIF
87         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
88            WRITE(numout,*)
89            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies '
90            WRITE(numout,*)
91         ENDIF
92         IF( .NOT.ln_trcdta ) THEN
93            WRITE(numout,*)
94            WRITE(numout,*) '  All the passive tracers are initialised with constant values '
95            WRITE(numout,*)
96         ENDIF
97      ENDIF
98
99     
100      rdttrc = rdt * FLOAT( nn_dttrc )   ! passive tracer time-step
101 
102      IF(lwp) THEN                   ! control print
103        WRITE(numout,*) 
104        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc
105        WRITE(numout,*) 
106      ENDIF
107
108
109#if defined key_trdmxl_trc || defined key_trdtrc
110
111         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
112         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
113905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
114
115         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
116         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
117906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
118         IF(lwm) WRITE ( numont, namtrc_trd )
119
120         IF(lwp) THEN
121            WRITE(numout,*)
122            WRITE(numout,*) ' trd_mxl_trc_init : read namelist namtrc_trd                    '
123            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
124            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
125            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
126            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart
127            WRITE(numout,*) '   * flag to diagnose trends of                                 '
128            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant
129            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
130            DO jn = 1, jptra
131               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
132            END DO
133         ENDIF
134#endif
135
136
137      ! Call the ice module for tracers
138      ! -------------------------------
139                                  CALL trc_nam_ice
140
141      ! namelist of SMS
142      ! ---------------     
143      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
144      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
145      ENDIF
146
147      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
148      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
149      ENDIF
150
151      IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers
152      ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used'
153      ENDIF
154
155      IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
156      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
157      ENDIF
158      !
159   END SUBROUTINE trc_nam
160
161
162   SUBROUTINE trc_nam_run
163      !!---------------------------------------------------------------------
164      !!                     ***  ROUTINE trc_nam  ***
165      !!
166      !! ** Purpose :   read options for the passive tracer run (namelist)
167      !!
168      !!---------------------------------------------------------------------
169      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, &
170        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out
171      !
172      INTEGER  ::   ios                 ! Local integer output status for namelist read
173      !!---------------------------------------------------------------------
174      !
175      IF(lwp) WRITE(numout,*) 'trc_nam_run : read the passive tracer namelists'
176      IF(lwp) WRITE(numout,*) '~~~~~~~'
177
178      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
179      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
180      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 )
181
182      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
183      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
184901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
185
186      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
187      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
188902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
189      IF(lwm) WRITE ( numont, namtrc_run )
190
191      !  computes the first time step of tracer model
192      nittrc000 = nit000 + nn_dttrc - 1
193
194      IF(lwp) THEN                   ! control print
195         WRITE(numout,*)
196         WRITE(numout,*) ' Namelist : namtrc_run'
197         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
198         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
199         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
200         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
201         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
202         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
203         WRITE(numout,*) ' '
204      ENDIF
205      !
206    END SUBROUTINE trc_nam_run
207
208
209   SUBROUTINE trc_nam_ice
210      !!---------------------------------------------------------------------
211      !!                     ***  ROUTINE trc_nam_ice ***
212      !!
213      !! ** Purpose :   Read the namelist for the ice effect on tracers
214      !!
215      !! ** Method  : -
216      !!
217      !!---------------------------------------------------------------------
218      INTEGER :: jn      ! dummy loop indices
219      INTEGER :: ios     ! Local integer output status for namelist read
220      !
221      TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer
222      !!
223      NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer
224      !!---------------------------------------------------------------------
225      !
226      IF(lwp) THEN
227         WRITE(numout,*)
228         WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice'
229         WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
230      ENDIF
231
232      IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice')
233
234      !
235      REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data
236      READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901)
237 901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp )
238
239      REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients
240      READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 )
241 902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp )
242
243      IF( lwp ) THEN
244         WRITE(numout,*) ' '
245         WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr
246         WRITE(numout,*) ' '
247      ENDIF
248
249      ! Assign namelist stuff
250      DO jn = 1, jptra
251         trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio
252         trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr
253         cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o
254      END DO
255
256      IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice')
257      !
258   END SUBROUTINE trc_nam_ice
259
260
261   SUBROUTINE trc_nam_trc
262      !!---------------------------------------------------------------------
263      !!                     ***  ROUTINE trc_nam  ***
264      !!
265      !! ** Purpose :   read options for the passive tracer run (namelist)
266      !!
267      !!---------------------------------------------------------------------
268      INTEGER  ::   ios                 ! Local integer output status for namelist read
269      INTEGER  ::   jn                  ! dummy loop indice
270      !
271      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput
272      !!
273      NAMELIST/namtrc/ sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo
274      !!---------------------------------------------------------------------
275      IF(lwp) WRITE(numout,*)
276      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists'
277      IF(lwp) WRITE(numout,*) '~~~~~~~'
278
279      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
280      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
281901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
282
283      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
284      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
285902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
286      IF(lwm) WRITE ( numont, namtrc )
287
288      DO jn = 1, jptra
289         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
290         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
291         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
292         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
293#if defined key_my_trc
294         ln_trc_sbc(jn) =       sn_tracer(jn)%llsbc
295         ln_trc_cbc(jn) =       sn_tracer(jn)%llcbc
296         ln_trc_obc(jn) =       sn_tracer(jn)%llobc
297#endif
298         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
299      END DO
300      !
301   END SUBROUTINE trc_nam_trc
302
303
304   SUBROUTINE trc_nam_dia
305      !!---------------------------------------------------------------------
306      !!                     ***  ROUTINE trc_nam_dia  ***
307      !!
308      !! ** Purpose :   read options for the passive tracer diagnostics
309      !!
310      !! ** Method  : - read passive tracer namelist
311      !!              - read namelist of each defined SMS model
312      !!                ( (PISCES, CFC, MY_TRC )
313      !!---------------------------------------------------------------------
314      INTEGER  ::   ios                 ! Local integer output status for namelist read
315      INTEGER ::  ierr
316      !!
317#if defined key_trdmxl_trc  || defined key_trdtrc
318      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
319         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, &
320         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
321#endif
322      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio
323      !!---------------------------------------------------------------------
324
325      IF(lwp) WRITE(numout,*)
326      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
327      IF(lwp) WRITE(numout,*) '~~~~~~~'
328
329      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
330      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
331903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
332
333      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
334      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
335904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
336      IF(lwm) WRITE ( numont, namtrc_dia )
337
338      IF(lwp) THEN
339         WRITE(numout,*)
340         WRITE(numout,*)
341         WRITE(numout,*) ' Namelist : namtrc_dia'
342         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
343         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
344         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
345         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
346         WRITE(numout,*) ' '
347      ENDIF
348
349      IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN
350         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
351           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
352           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
353         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
354         !
355         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
356         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
357         !
358      ENDIF
359
360      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN
361         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
362           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
363         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
364         !
365         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
366         !
367      ENDIF
368      !
369   END SUBROUTINE trc_nam_dia
370
371#else
372   !!----------------------------------------------------------------------
373   !!  Dummy module :                                     No passive tracer
374   !!----------------------------------------------------------------------
375CONTAINS
376   SUBROUTINE trc_nam                      ! Empty routine   
377   END SUBROUTINE trc_nam
378   SUBROUTINE trc_nam_run                      ! Empty routine   
379   END SUBROUTINE trc_nam_run
380#endif
381
382   !!----------------------------------------------------------------------
383   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
384   !! $Id$
385   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
386   !!======================================================================
387END MODULE trcnam
Note: See TracBrowser for help on using the repository browser.