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.
Changeset 8471 for branches/2017/nemo_v3_6_STABLE_trdtrc/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 – NEMO

Ignore:
Timestamp:
2017-08-29T18:12:42+02:00 (7 years ago)
Author:
jpalmier
Message:

JPALM -- #1933 -- add and correct passive tracer trends - needs improvements and testing

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/nemo_v3_6_STABLE_trdtrc/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r8353 r8471  
    5555      !! ** Method  : - read passive tracer namelist  
    5656      !!              - read namelist of each defined SMS model 
    57       !!                ( (PISCES, CFC, MY_TRC ) 
    58       !!--------------------------------------------------------------------- 
    59       INTEGER  ::   jn                  ! dummy loop indice 
     57      !!                ( (PISCES, CFC, MY_TRC, MEDUSA, IDTRA, Age ) 
     58      !!--------------------------------------------------------------------- 
     59      INTEGER ::  ierr 
     60#if defined key_trdmxl_trc  || defined key_trdtrc 
     61      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
     62         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, & 
     63         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
     64#endif 
     65 
     66      INTEGER  ::   jn, jk              ! dummy loop indice 
     67      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     68      !!--------------------------------------------------------------------- 
     69 
     70 
    6071      !                                        !   Parameters of the run  
    6172      IF( .NOT. lk_offline ) CALL trc_nam_run 
     
    145156      ENDIF 
    146157 
    147       ! 
    148    END SUBROUTINE trc_nam 
    149  
    150    SUBROUTINE trc_nam_run 
    151       !!--------------------------------------------------------------------- 
    152       !!                     ***  ROUTINE trc_nam  *** 
    153       !! 
    154       !! ** Purpose :   read options for the passive tracer run (namelist)  
    155       !! 
    156       !!--------------------------------------------------------------------- 
    157       NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
    158         &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
    159  
    160  
    161       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    162  
    163       !!--------------------------------------------------------------------- 
    164  
    165  
    166       IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
    167       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    168  
    169       CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    170       CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    171       IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 ) 
    172  
    173       REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    174       READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901) 
    175 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    176  
    177       REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
    178       READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 ) 
    179 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
    180       IF(lwm) WRITE ( numont, namtrc_run ) 
    181  
    182       !  computes the first time step of tracer model 
    183       nittrc000 = nit000 + nn_dttrc - 1 
    184  
    185       IF(lwp) THEN                   ! control print 
    186          WRITE(numout,*) 
    187          WRITE(numout,*) ' Namelist : namtrc_run' 
    188          WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
    189          WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
    190          WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
    191          WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
    192          WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc  
    193          WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    194          WRITE(numout,*) ' ' 
    195       ENDIF 
    196       ! 
    197     END SUBROUTINE trc_nam_run 
    198  
    199    SUBROUTINE trc_nam_ice 
    200       !!--------------------------------------------------------------------- 
    201       !!                     ***  ROUTINE trc_nam_ice *** 
    202       !! 
    203       !! ** Purpose :   Read the namelist for the ice effect on tracers 
    204       !! 
    205       !! ** Method  : - 
    206       !! 
    207       !!--------------------------------------------------------------------- 
    208       ! --- Variable declarations --- ! 
    209       INTEGER :: jn      ! dummy loop indices 
    210       INTEGER :: ios     ! Local integer output status for namelist read 
    211  
    212       ! --- Namelist declarations --- ! 
    213       TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer 
    214       NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer 
    215  
    216       IF(lwp) THEN 
    217          WRITE(numout,*) 
    218          WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice' 
    219          WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    220       ENDIF 
    221  
    222       IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice') 
    223  
    224       ! 
    225       REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data 
    226       READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901) 
    227  901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp ) 
    228  
    229       REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients 
    230       READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 ) 
    231  902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp ) 
    232  
    233       IF( lwp ) THEN 
    234          WRITE(numout,*) ' ' 
    235          WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr 
    236          WRITE(numout,*) ' ' 
    237       ENDIF 
    238  
    239       ! Assign namelist stuff 
    240       DO jn = 1, jptra 
    241          trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio 
    242          trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr 
    243          cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o 
    244       END DO 
    245  
    246       IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice') 
    247       ! 
    248    END SUBROUTINE trc_nam_ice 
    249  
    250    SUBROUTINE trc_nam_trc 
    251       !!--------------------------------------------------------------------- 
    252       !!                     ***  ROUTINE trc_nam  *** 
    253       !! 
    254       !! ** Purpose :   read options for the passive tracer run (namelist)  
    255       !! 
    256       !!--------------------------------------------------------------------- 
    257       TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
    258       !! 
    259       NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo 
    260    
    261       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    262       INTEGER  ::   jn                  ! dummy loop indice 
    263       !!--------------------------------------------------------------------- 
    264       IF(lwp) WRITE(numout,*) 
    265       IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
    266       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    267  
    268  
    269       REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    270       READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
    271 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    272  
    273       REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
    274       READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
    275 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
    276       IF(lwm) WRITE ( numont, namtrc ) 
    277  
    278       DO jn = 1, jptra 
    279          ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
    280          ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
    281          ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
    282          ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
    283          ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
    284       END DO 
    285        
    286     END SUBROUTINE trc_nam_trc 
    287  
    288  
    289    SUBROUTINE trc_nam_dia 
    290       !!--------------------------------------------------------------------- 
    291       !!                     ***  ROUTINE trc_nam_dia  *** 
    292       !! 
    293       !! ** Purpose :   read options for the passive tracer diagnostics 
    294       !! 
    295       !! ** Method  : - read passive tracer namelist  
    296       !!              - read namelist of each defined SMS model 
    297       !!                ( (PISCES, CFC, MY_TRC ) 
    298       !!--------------------------------------------------------------------- 
    299       INTEGER ::  ierr 
    300 #if defined key_trdmxl_trc  || defined key_trdtrc 
    301       NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
    302          &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, & 
    303          &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
    304 #endif 
    305       NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio 
    306  
    307       INTEGER  ::   jn         
    308       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    309       !!--------------------------------------------------------------------- 
    310  
    311       IF(lwp) WRITE(numout,*)  
    312       IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
    313       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    314  
    315       IF(lwp) WRITE(numout,*) 
    316       IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
    317       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    318  
    319       REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics 
    320       READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903) 
    321 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp ) 
    322  
    323       REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics 
    324       READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 ) 
    325 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp ) 
    326       IF(lwm) WRITE ( numont, namtrc_dia ) 
    327  
    328       IF(lwp) THEN 
    329          WRITE(numout,*) 
    330          WRITE(numout,*) 
    331          WRITE(numout,*) ' Namelist : namtrc_dia' 
    332          WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc 
    333          WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio 
    334          WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia 
    335          WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
    336          WRITE(numout,*) ' ' 
    337       ENDIF 
    338  
    339       IF( ln_diatrc ) THEN  
    340          ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
    341            &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
    342            &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr )  
    343          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' ) 
    344          ! 
    345          trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' '  
    346          trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' '  
    347          ! 
    348       ENDIF 
    349  
    350       IF( ln_diabio .OR. l_trdtrc ) THEN 
    351          ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , & 
    352            &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr )  
    353          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' ) 
    354          ! 
    355          trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' '  
    356          ! 
    357       ENDIF 
    358158 
    359159#if defined key_trdmxl_trc || defined key_trdtrc 
     
    384184#endif 
    385185      ! 
     186   END SUBROUTINE trc_nam 
     187 
     188   SUBROUTINE trc_nam_run 
     189      !!--------------------------------------------------------------------- 
     190      !!                     ***  ROUTINE trc_nam  *** 
     191      !! 
     192      !! ** Purpose :   read options for the passive tracer run (namelist)  
     193      !! 
     194      !!--------------------------------------------------------------------- 
     195      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
     196        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
     197 
     198 
     199      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     200 
     201      !!--------------------------------------------------------------------- 
     202 
     203 
     204      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     205      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     206 
     207      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     208      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     209      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 ) 
     210 
     211      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
     212      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901) 
     213901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
     214 
     215      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     216      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 ) 
     217902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     218      IF(lwm) WRITE ( numont, namtrc_run ) 
     219 
     220      !  computes the first time step of tracer model 
     221      nittrc000 = nit000 + nn_dttrc - 1 
     222 
     223      IF(lwp) THEN                   ! control print 
     224         WRITE(numout,*) 
     225         WRITE(numout,*) ' Namelist : namtrc_run' 
     226         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
     227         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
     228         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
     229         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
     230         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc  
     231         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
     232         WRITE(numout,*) ' ' 
     233      ENDIF 
     234      ! 
     235    END SUBROUTINE trc_nam_run 
     236 
     237   SUBROUTINE trc_nam_ice 
     238      !!--------------------------------------------------------------------- 
     239      !!                     ***  ROUTINE trc_nam_ice *** 
     240      !! 
     241      !! ** Purpose :   Read the namelist for the ice effect on tracers 
     242      !! 
     243      !! ** Method  : - 
     244      !! 
     245      !!--------------------------------------------------------------------- 
     246      ! --- Variable declarations --- ! 
     247      INTEGER :: jn      ! dummy loop indices 
     248      INTEGER :: ios     ! Local integer output status for namelist read 
     249 
     250      ! --- Namelist declarations --- ! 
     251      TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer 
     252      NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer 
     253 
     254      IF(lwp) THEN 
     255         WRITE(numout,*) 
     256         WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice' 
     257         WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     258      ENDIF 
     259 
     260      IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice') 
     261 
     262      ! 
     263      REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data 
     264      READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901) 
     265 901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp ) 
     266 
     267      REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients 
     268      READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 ) 
     269 902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp ) 
     270 
     271      IF( lwp ) THEN 
     272         WRITE(numout,*) ' ' 
     273         WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr 
     274         WRITE(numout,*) ' ' 
     275      ENDIF 
     276 
     277      ! Assign namelist stuff 
     278      DO jn = 1, jptra 
     279         trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio 
     280         trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr 
     281         cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o 
     282      END DO 
     283 
     284      IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice') 
     285      ! 
     286   END SUBROUTINE trc_nam_ice 
     287 
     288   SUBROUTINE trc_nam_trc 
     289      !!--------------------------------------------------------------------- 
     290      !!                     ***  ROUTINE trc_nam  *** 
     291      !! 
     292      !! ** Purpose :   read options for the passive tracer run (namelist)  
     293      !! 
     294      !!--------------------------------------------------------------------- 
     295      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
     296      !! 
     297      NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo 
     298   
     299      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     300      INTEGER  ::   jn                  ! dummy loop indice 
     301      !!--------------------------------------------------------------------- 
     302      IF(lwp) WRITE(numout,*) 
     303      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     304      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     305 
     306 
     307      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
     308      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
     309901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
     310 
     311      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     312      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
     313902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     314      IF(lwm) WRITE ( numont, namtrc ) 
     315 
     316      DO jn = 1, jptra 
     317         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
     318         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
     319         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
     320         ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
     321         ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
     322      END DO 
     323       
     324    END SUBROUTINE trc_nam_trc 
     325 
     326 
     327   SUBROUTINE trc_nam_dia 
     328      !!--------------------------------------------------------------------- 
     329      !!                     ***  ROUTINE trc_nam_dia  *** 
     330      !! 
     331      !! ** Purpose :   read options for the passive tracer diagnostics 
     332      !! 
     333      !! ** Method  : - read passive tracer namelist  
     334      !!              - read namelist of each defined SMS model 
     335      !!                ( (PISCES, CFC, MY_TRC ) 
     336      !!--------------------------------------------------------------------- 
     337      INTEGER ::  ierr 
     338#if defined key_trdmxl_trc  || defined key_trdtrc 
     339      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
     340         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, & 
     341         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
     342#endif 
     343      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio 
     344 
     345      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     346      !!--------------------------------------------------------------------- 
     347 
     348      IF(lwp) WRITE(numout,*)  
     349      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
     350      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     351 
     352      IF(lwp) WRITE(numout,*) 
     353      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
     354      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     355 
     356      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics 
     357      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903) 
     358903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp ) 
     359 
     360      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics 
     361      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 ) 
     362904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp ) 
     363      IF(lwm) WRITE ( numont, namtrc_dia ) 
     364 
     365      IF(lwp) THEN 
     366         WRITE(numout,*) 
     367         WRITE(numout,*) 
     368         WRITE(numout,*) ' Namelist : namtrc_dia' 
     369         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc 
     370         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio 
     371         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia 
     372         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
     373         WRITE(numout,*) ' ' 
     374      ENDIF 
     375 
     376      IF( ln_diatrc ) THEN  
     377         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
     378           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
     379           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr )  
     380         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' ) 
     381         ! 
     382         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' '  
     383         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' '  
     384         ! 
     385      ENDIF 
     386 
     387      IF( ln_diabio .OR. l_trdtrc ) THEN 
     388         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , & 
     389           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr )  
     390         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' ) 
     391         ! 
     392         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' '  
     393         ! 
     394      ENDIF 
     395      ! 
    386396   END SUBROUTINE trc_nam_dia 
    387397 
Note: See TracChangeset for help on using the changeset viewer.