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 NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/trcnam.F90 @ 11954

Last change on this file since 11954 was 11648, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Introduce broadcast of namelist character buffer from single reader to all others. This completes the second stage but there is still an issue with AGRIF that may scupper this whole concept

  • Property svn:keywords set to Id
File size: 13.7 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   !!----------------------------------------------------------------------
[9169]20   USE oce_trc     ! shared variables between ocean and passive tracers
21   USE trc         ! passive tracers common variables
22   USE trd_oce     !       
23   USE trdtrc_oce  !
24   USE iom         ! I/O manager
[10425]25#if defined key_mpp_mpi
26   USE lib_mpp, ONLY: ncom_dttrc
27#endif
[2038]28
29   IMPLICIT NONE
30   PRIVATE
31
[9169]32   PUBLIC   trc_nam_run  ! called in trcini
33   PUBLIC   trc_nam      ! called in trcini
[2038]34
[9169]35   TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  !: type of tracer for saving if not key_iomput
[7646]36
[2038]37   !!----------------------------------------------------------------------
[10067]38   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[5341]39   !! $Id$
[10068]40   !! Software governed by the CeCILL license (see ./LICENSE)
[2038]41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE trc_nam
45      !!---------------------------------------------------------------------
46      !!                     ***  ROUTINE trc_nam  ***
47      !!
48      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
49      !!
50      !! ** Method  : - read passive tracer namelist
51      !!              - read namelist of each defined SMS model
[3680]52      !!                ( (PISCES, CFC, MY_TRC )
[2038]53      !!---------------------------------------------------------------------
[9169]54      INTEGER  ::   jn   ! dummy loop indice
55      !!---------------------------------------------------------------------
[7646]56      !
57      IF( .NOT.l_offline )   CALL trc_nam_run     ! Parameters of the run                                 
[5836]58      !               
[9169]59      CALL trc_nam_trc                            ! passive tracer informations
[5836]60      !                                       
[9169]61      IF( ln_rsttr                     )   ln_trcdta = .FALSE.   ! restart : no need of clim data
[4152]62      !
[9169]63      IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta = .TRUE.    ! damping : need to have clim data
[5836]64      !
[9169]65      !
[5836]66      IF(lwp) THEN                   ! control print
[3294]67         IF( ln_rsttr ) THEN
68            WRITE(numout,*)
[9169]69            WRITE(numout,*) '   ==>>>   Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
[3294]70         ENDIF
[4148]71         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
72            WRITE(numout,*)
[9169]73            WRITE(numout,*) '   ==>>>   Some of the passive tracers are initialised from climatologies '
[4148]74         ENDIF
75         IF( .NOT.ln_trcdta ) THEN
76            WRITE(numout,*)
[9169]77            WRITE(numout,*) '   ==>>>   All the passive tracers are initialised with constant values '
[4148]78         ENDIF
[3294]79      ENDIF
[7646]80      !
[10425]81      rdttrc = rdt * FLOAT( nn_dttrc )          ! passive tracer time-step     
[7646]82      !
83      IF(lwp) THEN                              ! control print
[4152]84        WRITE(numout,*) 
[9169]85        WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = nn_dttrc*rdt = ', rdttrc
[4152]86      ENDIF
[2038]87      !
[7646]88      IF( l_trdtrc )        CALL trc_nam_trd    ! Passive tracer trends
89      !
[2038]90   END SUBROUTINE trc_nam
91
[5836]92
[4152]93   SUBROUTINE trc_nam_run
94      !!---------------------------------------------------------------------
95      !!                     ***  ROUTINE trc_nam  ***
96      !!
97      !! ** Purpose :   read options for the passive tracer run (namelist)
98      !!
99      !!---------------------------------------------------------------------
[9169]100      INTEGER  ::   ios   ! Local integer
101      !!
[7646]102      NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, &
[5341]103        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out
[4152]104      !!---------------------------------------------------------------------
[5836]105      !
[9169]106      IF(lwp) WRITE(numout,*)
[6140]107      IF(lwp) WRITE(numout,*) 'trc_nam_run : read the passive tracer namelists'
[9169]108      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
109      !
[11648]110      CALL load_nml( numnat_ref, 'namelist_top_ref' , numout, lwm )
111      CALL load_nml( numnat_cfg, 'namelist_top_cfg' , numout, lwm )
[4624]112      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 )
[9169]113      !
[4152]114      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
[11536]115901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' )
[4152]116      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
[11536]117902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' )
[9169]118      IF(lwm) WRITE( numont, namtrc_run )
[4152]119
[9169]120      nittrc000 = nit000 + nn_dttrc - 1      ! first time step of tracer model
[4152]121
122      IF(lwp) THEN                   ! control print
[9169]123         WRITE(numout,*) '   Namelist : namtrc_run'
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,*) '      Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
[4152]129      ENDIF
130      !
[10425]131#if defined key_mpp_mpi
132      ncom_dttrc = nn_dttrc    ! make nn_fsbc available for lib_mpp
133#endif
134      !
135   END SUBROUTINE trc_nam_run
[4152]136
[9169]137
[4152]138   SUBROUTINE trc_nam_trc
139      !!---------------------------------------------------------------------
140      !!                     ***  ROUTINE trc_nam  ***
141      !!
142      !! ** Purpose :   read options for the passive tracer run (namelist)
143      !!
144      !!---------------------------------------------------------------------
[9169]145      INTEGER ::   ios, ierr, icfc       ! Local integer
[4152]146      !!
[7646]147      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, &
148         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d
[4152]149      !!---------------------------------------------------------------------
[7646]150      ! Dummy settings to fill tracers data structure
151      !                  !   name   !   title   !   unit   !   init  !   sbc   !   cbc   !   obc  !
152      sn_tracer = PTRACER( 'NONAME' , 'NOTITLE' , 'NOUNIT' , .false. , .false. , .false. , .false.)
153      !
[4152]154      IF(lwp) WRITE(numout,*)
[6140]155      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists'
[9169]156      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
[4152]157
158      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
[11536]159901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' )
[4152]160      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
[11536]161902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' )
[9169]162      IF(lwm) WRITE( numont, namtrc )
[4152]163
[7646]164      ! Control settings
165      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' )
166      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jp_bgc = 0
167      ll_cfc = ln_cfc11 .OR. ln_cfc12 .OR. ln_sf6
[5836]168      !
[7646]169      jptra       =  0
170      jp_pisces   =  0    ;   jp_pcs0  =  0    ;   jp_pcs1  = 0
171      jp_my_trc   =  0    ;   jp_myt0  =  0    ;   jp_myt1  = 0
172      jp_cfc      =  0    ;   jp_cfc0  =  0    ;   jp_cfc1  = 0
173      jp_age      =  0    ;   jp_c14   =  0
174      !
175      IF( ln_pisces )  THEN
176         jp_pisces = jp_bgc
177         jp_pcs0   = 1
178         jp_pcs1   = jp_pisces
179      ENDIF
180      IF( ln_my_trc )  THEN
181          jp_my_trc = jp_bgc
182          jp_myt0   = 1
183          jp_myt1   = jp_my_trc
184      ENDIF
185      !
186      jptra  = jp_bgc
187      !
188      IF( ln_age )    THEN
189         jptra     = jptra + 1
190         jp_age    = jptra
191      ENDIF
192      IF( ln_cfc11 )  jp_cfc = jp_cfc + 1
193      IF( ln_cfc12 )  jp_cfc = jp_cfc + 1
194      IF( ln_sf6   )  jp_cfc = jp_cfc + 1
195      IF( ll_cfc )    THEN
196          jptra     = jptra + jp_cfc
197          jp_cfc0   = jptra - jp_cfc + 1
198          jp_cfc1   = jptra
199      ENDIF
200      IF( ln_c14 )    THEN
201           jptra     = jptra + 1
202           jp_c14    = jptra
203      ENDIF
204      !
205      IF( jptra == 0 )   CALL ctl_stop( 'All TOP tracers disabled: change namtrc setting or check if key_top is active' )
206      !
207      IF(lwp) THEN                   ! control print
[9169]208         WRITE(numout,*) '   Namelist : namtrc'
209         WRITE(numout,*) '      Total number of passive tracers              jptra         = ', jptra
210         WRITE(numout,*) '      Total number of BGC tracers                  jp_bgc        = ', jp_bgc
211         WRITE(numout,*) '      Simulating PISCES model                      ln_pisces     = ', ln_pisces
212         WRITE(numout,*) '      Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc
213         WRITE(numout,*) '      Simulating water mass age                    ln_age        = ', ln_age
214         WRITE(numout,*) '      Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11
215         WRITE(numout,*) '      Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12
216         WRITE(numout,*) '      Simulating SF6 passive tracer                ln_sf6        = ', ln_sf6
217         WRITE(numout,*) '      Total number of CFCs tracers                 jp_cfc        = ', jp_cfc
218         WRITE(numout,*) '      Simulating C14   passive tracer              ln_c14        = ', ln_c14
219         WRITE(numout,*) '      Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
220         WRITE(numout,*) '      Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
221         WRITE(numout,*) '      Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
[7646]222      ENDIF
223      !
224      IF( ll_cfc .OR. ln_c14 ) THEN
225        !                             ! Open namelist files
[11648]226        CALL load_nml( numtrc_ref, 'namelist_trc_ref' , numout, lwm )
227        CALL load_nml( numtrc_cfg, 'namelist_trc_cfg' , numout, lwm )
[7646]228        IF(lwm) CALL ctl_opn( numonr, 'output.namelist.trc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
229        !
230      ENDIF
[9169]231      !
[5836]232   END SUBROUTINE trc_nam_trc
[4152]233
[9169]234
[7646]235   SUBROUTINE trc_nam_trd
[4152]236      !!---------------------------------------------------------------------
237      !!                     ***  ROUTINE trc_nam_dia  ***
238      !!
239      !! ** Purpose :   read options for the passive tracer diagnostics
240      !!
241      !! ** Method  : - read passive tracer namelist
242      !!              - read namelist of each defined SMS model
243      !!                ( (PISCES, CFC, MY_TRC )
244      !!---------------------------------------------------------------------
[7646]245#if defined key_trdmxl_trc  || defined key_trdtrc
[9169]246      INTEGER  ::   ios, ierr                 ! Local integer
[5836]247      !!
[4152]248      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
[4990]249         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, &
[4152]250         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
251      !!---------------------------------------------------------------------
[9169]252      !
[4152]253      IF(lwp) WRITE(numout,*)
[7646]254      IF(lwp) WRITE(numout,*) 'trc_nam_trd : read the passive tracer diagnostics options'
[9169]255      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
[7646]256      !
257      ALLOCATE( ln_trdtrc(jptra) ) 
258      !
259      READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
[11536]260905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_trd in reference namelist' )
[7646]261      READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
[11536]262906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist' )
[9169]263      IF(lwm) WRITE( numont, namtrc_trd )
[4152]264
265      IF(lwp) THEN
[9169]266         WRITE(numout,*) '   Namelist : namtrc_trd                    '
267         WRITE(numout,*) '      frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
268         WRITE(numout,*) '      control surface type              nn_ctls_trc            = ', nn_ctls_trc
269         WRITE(numout,*) '      restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart
270         WRITE(numout,*) '      instantantaneous or mean trends   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant
271         WRITE(numout,*) '      unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
[7646]272         DO jn = 1, jptra
[9169]273            IF( ln_trdtrc(jn) ) WRITE(numout,*) '      compute ML trends for tracer number :', jn
[7646]274         END DO
[4152]275      ENDIF
[7646]276#endif
[4152]277      !
[7646]278   END SUBROUTINE trc_nam_trd
[4152]279
[2038]280#else
281   !!----------------------------------------------------------------------
282   !!  Dummy module :                                     No passive tracer
283   !!----------------------------------------------------------------------
284CONTAINS
285   SUBROUTINE trc_nam                      ! Empty routine   
286   END SUBROUTINE trc_nam
[4152]287   SUBROUTINE trc_nam_run                      ! Empty routine   
288   END SUBROUTINE trc_nam_run
[2038]289#endif
290
291   !!======================================================================
[5656]292END MODULE trcnam
Note: See TracBrowser for help on using the repository browser.