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 7873 – NEMO

Changeset 7873


Ignore:
Timestamp:
2017-04-05T11:24:00+02:00 (7 years ago)
Author:
cetlod
Message:

v3.6stable: minor corrections to avoid compilation errors when using 3D trends diagnostics in TOP

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

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