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

source: branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 3875

Last change on this file since 3875 was 3875, checked in by clevy, 11 years ago

Configuration Setting/Step? 1, see ticket:#1074

  • Property svn:keywords set to Id
File size: 13.7 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, ln_trcdmp, &
63         &             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      ! Namelist nattrc (files)
81      ! ----------------------------------------------
82      nn_dttrc      = 1                 ! default values
83      nn_writetrc   = 10 
84      ln_top_euler  = .FALSE.
85      ln_rsttr      = .FALSE.
86      nn_rsttr      =  0
87      cn_trcrst_in  = 'restart_trc'
88      cn_trcrst_out = 'restart_trc'
89      !
90      DO jn = 1, jptra
91         WRITE( sn_tracer(jn)%clsname,'("TR_",I1)'           ) jn
92         WRITE( sn_tracer(jn)%cllname,'("TRACER NUMBER ",I1)') jn
93         sn_tracer(jn)%clunit  = 'mmole/m3'
94         sn_tracer(jn)%llinit  = .FALSE.
95         sn_tracer(jn)%llsave  = .TRUE.
96      END DO
97      ln_trcdta = .FALSE.
98      ln_trcdmp = .FALSE.
99
100      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
101      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
102901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
103
104      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
105      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
106902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
107      WRITE ( numont, namtrc )
108
109      DO jn = 1, jptra
110         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
111         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
112         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
113         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
114         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
115      END DO
116
117      !!KPE  computes the first time step of tracer model
118      nittrc000 = nit000 + nn_dttrc - 1
119 
120
121      IF(lwp) THEN                   ! control print
122         WRITE(numout,*)
123         WRITE(numout,*) ' Namelist : namtrc'
124         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
125         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
126         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
127         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
128         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
129         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
130         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
131         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
132         WRITE(numout,*) ' '
133         DO jn = 1, jptra
134            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
135         END DO
136         WRITE(numout,*) ' '
137      ENDIF
138
139      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step
140 
141      IF(lwp) THEN                   ! control print
142        WRITE(numout,*) 
143        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1)
144        WRITE(numout,*) 
145      ENDIF
146
147      ln_diatrc = .FALSE.
148      ln_diabio = .FALSE.
149      nn_writedia = 10
150      nn_writebio = 10
151
152      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
153      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
154903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
155
156      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
157      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
158904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
159      WRITE ( numont, namtrc_dia )
160
161      IF(lwp) THEN
162         WRITE(numout,*)
163         WRITE(numout,*)
164         WRITE(numout,*) ' Namelist : namtrc_dia'
165         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
166         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
167         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
168         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
169         WRITE(numout,*) ' '
170      ENDIF
171
172      IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN
173         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
174           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
175           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
176         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
177         !
178         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
179         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
180         !
181      ENDIF
182
183      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN
184         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
185           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
186         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
187         !
188         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
189         !
190      ENDIF
191
192      ! namelist of transport
193      ! ---------------------
194      CALL trc_nam_trp
195
196
197      IF( ln_trcdmp .AND. .NOT.ln_trcdta ) THEN
198         CALL ctl_warn( 'trc_nam: passive tracer damping requires data from files we set ln_trcdta to TRUE' )
199         ln_trcdta = .TRUE.
200      ENDIF
201      !
202      IF( ln_rsttr .AND. .NOT.ln_trcdmp .AND. ln_trcdta ) THEN
203          CALL ctl_warn( 'trc_nam: passive tracer restart and  data intialisation, ',   &
204             &           'we keep the restart values and set ln_trcdta to FALSE' )
205         ln_trcdta = .FALSE.
206      ENDIF
207      !
208      IF( .NOT.ln_trcdta ) THEN
209         ln_trc_ini(:) = .FALSE.
210      ENDIF
211
212      IF(lwp) THEN                   ! control print
213         IF( ln_rsttr ) THEN
214            WRITE(numout,*)
215            WRITE(numout,*) '    read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
216            WRITE(numout,*)
217         ELSE
218            IF( .NOT.ln_trcdta ) THEN
219                WRITE(numout,*)
220                WRITE(numout,*) '  All the passive tracers are initialised with constant values '
221                WRITE(numout,*)
222            ENDIF
223         ENDIF
224      ENDIF
225
226
227#if defined key_trdmld_trc || defined key_trdtrc
228         nn_trd_trc  = 20
229         nn_ctls_trc =  9
230         rn_ucf_trc   =  1.
231         ln_trdmld_trc_instant = .TRUE.
232         ln_trdmld_trc_restart =.FALSE.
233         cn_trdrst_trc_in  = "restart_mld_trc"
234         cn_trdrst_trc_out = "restart_mld_trc"
235         ln_trdtrc(:) = .FALSE.
236
237         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
238         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
239905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
240
241         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
242         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
243906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
244         WRITE ( numont, namtrc_trd )
245
246         IF(lwp) THEN
247            WRITE(numout,*)
248            WRITE(numout,*) ' trd_mld_trc_init : read namelist namtrc_trd                    '
249            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
250            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
251            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
252            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmld_trc_restart  = ', ln_trdmld_trc_restart
253            WRITE(numout,*) '   * flag to diagnose trends of                                 '
254            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmld_trc_instant  = ', ln_trdmld_trc_instant
255            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
256            DO jn = 1, jptra
257               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
258            END DO
259         ENDIF
260#endif
261
262
263      ! namelist of SMS
264      ! ---------------     
265      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
266      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
267      ENDIF
268
269      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
270      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
271      ENDIF
272
273      IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers
274      ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used'
275      ENDIF
276
277      IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
278      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
279      ENDIF
280      !
281   END SUBROUTINE trc_nam
282
283#else
284   !!----------------------------------------------------------------------
285   !!  Dummy module :                                     No passive tracer
286   !!----------------------------------------------------------------------
287CONTAINS
288   SUBROUTINE trc_nam                      ! Empty routine   
289   END SUBROUTINE trc_nam
290#endif
291
292   !!----------------------------------------------------------------------
293   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
294   !! $Id$
295   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
296   !!======================================================================
297END MODULE  trcnam
Note: See TracBrowser for help on using the repository browser.