Ignore:
Timestamp:
Jul 14, 2020 12:06:09 PM (4 years ago)
Author:
suehring
Message:

Chemistry: Bugfix in variable name separation in profile-output initialization; Bugfix in counting the number of chemistry profiles; Surface-data output: Minor simplification in name creation for IO variables in restart files; init_grid: minor formatting adjustments

File:
1 edited

Legend:

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

    r4581 r4601  
    2121! Current revisions:
    2222! -----------------
    23 ! 
    24 ! 
     23!
     24!
    2525! Former revisions:
    2626! -----------------
    2727! $Id$
     28! - Bugfix in variable name separation in profile-output initialization
     29! - Bugfix in counting the number of chemistry profiles
     30!
     31! 4581 2020-06-29 08:49:58Z suehring
    2832! Enable output of resolved-scale vertical fluxes of chemical species.
    2933!
     
    11091113                cs_pr_count_sp                 = cs_pr_count_sp + 1
    11101114                cs_pr_index_sp(cs_pr_count_sp) = lsp
    1111                 dopr_index(var_count)          = pr_palm + cs_pr_count_sp + cs_pr_count_fl_sgs + cs_pr_count_fl_res
     1115                dopr_index(var_count)          = pr_palm + cs_pr_count_sp +                        &
     1116                                                 cs_pr_count_fl_sgs + cs_pr_count_fl_res
    11121117                dopr_unit                      = 'ppm'
    11131118                IF ( spec_name(1:2) == 'PM')  THEN
    11141119                   dopr_unit = 'kg m-3'
    11151120                ENDIF
    1116                 hom(:,2, dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
     1121                hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
    11171122                unit                              = dopr_unit
    11181123
     
    11251130          IF ( TRIM( variable(1:5) ) == 'kc_w"' )  THEN
    11261131             DO  lsp = 1, nspec
    1127                 index_start = INDEX( TRIM( variable ), TRIM( chem_species(lsp)%name ) )
    11281132                index_end   = LEN( TRIM( variable ) ) - 1
    1129                 IF ( index_start /= 0 )  THEN
    1130                    spec_name = TRIM( variable(index_start:index_end) )
    1131                    IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
    1132                       cs_pr_count_fl_sgs                     = cs_pr_count_fl_sgs + 1
    1133                       cs_pr_index_fl_sgs(cs_pr_count_fl_sgs) = lsp
    1134                       dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +          &
    1135                                                                cs_pr_count_fl_sgs +                &
    1136                                                                cs_pr_count_fl_res
    1137                       dopr_unit                              = 'm ppm s-1'
    1138                       IF ( spec_name(1:2) == 'PM')  THEN
    1139                          dopr_unit = 'kg m-2 s-1'
    1140                       ENDIF
    1141                       hom(:,2, dopr_index(var_count),:)    = SPREAD( zu, 2, statistic_regions+1 )
    1142                       unit                                 = dopr_unit
    1143 
    1144                       hom_index_fl_sgs(cs_pr_count_fl_sgs) = dopr_index(var_count)
     1133                index_start = 6
     1134                spec_name = TRIM( variable(index_start:index_end) )
     1135                IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
     1136                   cs_pr_count_fl_sgs                     = cs_pr_count_fl_sgs + 1
     1137                   cs_pr_index_fl_sgs(cs_pr_count_fl_sgs) = lsp
     1138                   dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +          &
     1139                                                            cs_pr_count_fl_sgs +                &
     1140                                                            cs_pr_count_fl_res
     1141                   dopr_unit                              = 'm ppm s-1'
     1142                   IF ( spec_name(1:2) == 'PM')  THEN
     1143                      dopr_unit = 'kg m-2 s-1'
    11451144                   ENDIF
     1145                   hom(:,2,dopr_index(var_count),:)     = SPREAD( zu, 2, statistic_regions+1 )
     1146                   unit                                 = dopr_unit
     1147
     1148                   hom_index_fl_sgs(cs_pr_count_fl_sgs) = dopr_index(var_count)
    11461149                ENDIF
    11471150             ENDDO
     
    11521155             spec_name = TRIM( variable(6:) )
    11531156             DO  lsp = 1, nspec
    1154                 index_start = INDEX( TRIM( variable ), TRIM( chem_species(lsp)%name ) )
     1157                index_start = 6
    11551158                index_end   = LEN( TRIM( variable ) ) - 1
    1156                 IF ( index_start /= 0 )  THEN
    1157                    spec_name = TRIM( variable(index_start:index_end) )
    1158                    IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
    1159                       cs_pr_count_fl_res                     = cs_pr_count_fl_res + 1
    1160                       cs_pr_index_fl_res(cs_pr_count_fl_res) = lsp
    1161                       dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +          &
    1162                                                                cs_pr_count_fl_sgs +                &
    1163                                                                cs_pr_count_fl_res
    1164                       dopr_unit                              = 'm ppm s-1'
    1165                       IF ( spec_name(1:2) == 'PM')  THEN
    1166                          dopr_unit = 'kg m-2 s-1'
    1167                       ENDIF
    1168                       hom(:,2, dopr_index(var_count),:)    = SPREAD( zu, 2, statistic_regions+1 )
    1169                       unit                                 = dopr_unit
    1170 
    1171                       hom_index_fl_res(cs_pr_count_fl_res) = dopr_index(var_count)
     1159                spec_name = TRIM( variable(index_start:index_end) )
     1160                IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
     1161                   cs_pr_count_fl_res                     = cs_pr_count_fl_res + 1
     1162                   cs_pr_index_fl_res(cs_pr_count_fl_res) = lsp
     1163                   dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +             &
     1164                                                            cs_pr_count_fl_sgs +                   &
     1165                                                            cs_pr_count_fl_res
     1166                   dopr_unit                              = 'm ppm s-1'
     1167                   IF ( spec_name(1:2) == 'PM')  THEN
     1168                      dopr_unit = 'kg m-2 s-1'
    11721169                   ENDIF
     1170                   hom(:,2, dopr_index(var_count),:)    = SPREAD( zu, 2, statistic_regions+1 )
     1171                   unit                                 = dopr_unit
     1172
     1173                   hom_index_fl_res(cs_pr_count_fl_res) = dopr_index(var_count)
    11731174                ENDIF
    11741175             ENDDO
     
    27102711    i = 1
    27112712
    2712     DO  WHILE ( data_output_pr(i)  /= ' '  .AND.  i <= 100 )
    2713 
     2713    DO  WHILE ( data_output_pr(i)  /= ' '  .AND.  i <= SIZE( data_output_pr ) )
    27142714       IF ( TRIM( data_output_pr(i)(1:3) ) == 'kc_' )  THEN
    27152715          max_pr_cs_tmp = max_pr_cs_tmp+1
Note: See TracChangeset for help on using the changeset viewer.