Ignore:
Timestamp:
Feb 19, 2021 10:05:08 PM (3 years ago)
Author:
forkel
Message:

removed unused parameters and write statements in chemistry

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4860 r4881  
    2626! -----------------
    2727! $Id$
     28! removed unnecessarty namelist parameters and commented output statements
     29! and cs_surface_initial_change
     30!
     31!
     32! 4860 2021-02-01 08:10:59Z raasch
    2833! further re-numbering of message IDs
    2934!
     
    297302! ------------
    298303!> Chemistry model for PALM-4U
    299 !> @todo Extend chem_species type by nspec and nvar as addititional elements (RF)
    300 !> @todo Check possibility to reduce dimension of chem_species%conc from nspec to nvar (RF)
    301304!> @todo Adjust chem_rrd_local to CASE structure of others modules. It is not allowed to use the
    302305!>       chemistry model in a precursor run and additionally not using it in a main run
     
    308311!> @todo slight differences in passive scalar and chem spcs when chem reactions turned off. Need to
    309312!>       be fixed. bK
    310 !> @todo test nesting for chem spcs, was implemented by suehring (kanani)
    311313!> @todo chemistry error messages
    312314!
     
    15211523                  (variable(char_len-2:) == '_xz')  .OR.                                           &
    15221524                  (variable(char_len-2:) == '_yz') ) )  THEN
    1523 !
    1524 !--   todo: remove or replace by "CALL message" mechanism (kanani)
    1525 !                    IF(myid == 0)  WRITE(6,*) 'Output of species ' // TRIM( variable )  //       &
    1526 !                                                             TRIM( chem_species(lsp)%name )
    15271525             IF (av == 0)  THEN
    15281526                DO  i = nxl, nxr
     
    16381636      DO  lsp = 1, nspec
    16391637         IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
    1640 !
    1641 !--   todo: remove or replace by "CALL message" mechanism (kanani)
    1642 !              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM( variable )  // &
    1643 !                                                           TRIM( chem_species(lsp)%name )
    16441638            IF (av == 0)  THEN
    16451639               DO  i = nxl, nxr
     
    17171711    DO  lsp=1,nspec
    17181712       IF (TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
    1719 !
    1720 !-- todo: remove or replace by "CALL message" mechanism (kanani)
    1721 !              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM( variable )  // &
    1722 !                                                        TRIM( chem_species(lsp)%name )
    17231713          IF (av == 0)  THEN
    17241714             IF ( .NOT. mask_surface(mid) )  THEN
     
    22722262       ENDIF
    22732263!
    2274 !--    If required, change the surface chem spcs at the start of the 3D run
    2275        IF ( cs_surface_initial_change(1) /= 0.0_wp )  THEN
    2276           DO  lsp = 1, nspec
    2277              DO  i = nxlg, nxrg
    2278                 DO  j = nysg, nyng
    2279                    flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzb,j,i), 0 ) )
    2280                    chem_species(lsp)%conc(nzb,j,i) = chem_species(lsp)%conc(nzb,j,i) +             &
    2281                                                      cs_surface_initial_change(lsp) * flag
    2282                 ENDDO
    2283              ENDDO
    2284           ENDDO
    2285        ENDIF
    2286 
    22872264    ENDIF
    22882265!
     
    22952272    DO  lsp = 1, nphot
    22962273       phot_frequen(lsp)%name = phot_names(lsp)
    2297 !
    2298 !-- todo: remove or replace by "CALL message" mechanism (kanani)
    2299 !--       IF( myid == 0 )  THEN
    2300 !--          WRITE(6,'(a,i4,3x,a)')  'Photolysis: ',lsp,TRIM( phot_names(lsp) )
    2301 !--       ENDIF
    23022274       phot_frequen(lsp)%freq(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  =>  freq_1(:,:,:,lsp)
    23032275    ENDDO
     
    25462518         bc_cs_t,                                                                                  &
    25472519         call_chem_at_all_substeps,                                                                &
    2548          chem_debug0,                                                                              &
    2549          chem_debug1,                                                                              &
    2550          chem_debug2,                                                                              &
    25512520         chem_gasphase_on,                                                                         &
    25522521         chem_mechanism,                                                                           &
     
    25552524         cs_profile,                                                                               &
    25562525         cs_surface,                                                                               &
    2557          cs_surface_initial_change,                                                                &
    2558          cs_vertical_gradient_level,                                                               &
    25592526         daytype_mdh,                                                                              &
    25602527         deposition_dry,                                                                           &
     
    25752542         photolysis_scheme,                                                                        &
    25762543         wall_csflux,                                                                              &
    2577          cs_vertical_gradient,                                                                     &
    2578          top_csflux,                                                                               &
    25792544         surface_csflux,                                                                           &
    25802545         surface_csflux_name,                                                                      &
Note: See TracChangeset for help on using the changeset viewer.