Changeset 4029 for palm/trunk/SOURCE


Ignore:
Timestamp:
Jun 14, 2019 2:04:35 PM (5 years ago)
Author:
raasch
Message:

bugfix: decycling of chemistry species after nesting data transfer, exchange of ghost points and boundary conditions separated for chemical species and SALSA module, nest_chemistry option removed, netcdf variable NF90_NOFILL is used as argument instead of 1 in calls to NF90_DEF_VAR_FILL

Location:
palm/trunk/SOURCE
Files:
5 edited

Legend:

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

    r4004 r4029  
    2727! -----------------
    2828! $Id$
     29! nest_chemistry option removed
     30!
     31! 4004 2019-05-24 11:32:38Z suehring
    2932! in subroutine chem_parin check emiss_lod / mod_emis only
    3033! when emissions_anthropogenic is activated in namelist (E.C. Chan)
     
    374377    SAVE
    375378
    376     LOGICAL ::  nest_chemistry = .TRUE.  !< flag for nesting mode of chemical species, independent on parent or not
    377 
    378379    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_1  !< pointer for swapping of timelevels for conc
    379380    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_2  !< pointer for swapping of timelevels for conc
     
    466467         3.25, -999., 2.8, 4.5/)
    467468
    468     PUBLIC nest_chemistry
    469469    PUBLIC nreact
    470470    PUBLIC nspec               !< number of gas phase chemical species including constant compound (e.g. N2)
     
    22342234         mode_emis,                        &
    22352235         my_steps,                         &
    2236          nest_chemistry,                   &
    22372236         rcntrl,                           &
    22382237         side_street_id,                   &
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r3995 r4029  
    2525! -----------------
    2626! $Id$
     27! netcdf variable NF90_NOFILL is used as argument instead of "1" in calls to NF90_DEF_VAR_FILL
     28!
     29! 3995 2019-05-22 18:59:54Z suehring
    2730! output of turbulence intensity added
    2831!
     
    20162019                nc_stat = NF90_DEF_VAR_FILL( id_set_3d(av),     &
    20172020                                             id_var_do3d(av,i), &
    2018                                              1, 0 )
     2021                                             NF90_NOFILL, 0 )
    20192022                CALL netcdf_handle_error( 'netcdf_define_header', 532 )
    20202023!
     
    30003003                   nc_stat = NF90_DEF_VAR_FILL( id_set_xy(av),     &
    30013004                                                id_var_do2d(av,i), &
    3002                                                 1, 0 )
     3005                                                NF90_NOFILL, 0 )
    30033006                   CALL netcdf_handle_error( 'netcdf_define_header', 533 )
    30043007!
     
    38883891                   nc_stat = NF90_DEF_VAR_FILL( id_set_xz(av),     &
    38893892                                                id_var_do2d(av,i), &
    3890                                                 1, 0 )
     3893                                                NF90_NOFILL, 0 )
    38913894                   CALL netcdf_handle_error( 'netcdf_define_header', 534 )
    38923895!
     
    47444747                   nc_stat = NF90_DEF_VAR_FILL( id_set_yz(av),     &
    47454748                                                id_var_do2d(av,i), &
    4746                                                 1, 0 )
     4749                                                NF90_NOFILL, 0 )
    47474750                   CALL netcdf_handle_error( 'netcdf_define_header', 535 )
    47484751!
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r4026 r4029  
    2525! -----------------
    2626! $Id$
     27! nest_chemistry switch removed
     28!
     29! 4026 2019-06-12 16:50:15Z suehring
    2730! Masked topography at boundary grid points in mass conservation, in order to
    2831! avoid that mean velocities within topography are imposed
     
    465468
    466469    USE chemistry_model_mod,                                                   &
    467         ONLY:  nest_chemistry, spec_conc_2
     470        ONLY:  spec_conc_2
    468471
    469472    USE cpulog,                                                                &
     
    14291432       ENDIF
    14301433       
    1431        IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     1434       IF ( air_chemistry )  THEN
    14321435          DO n = 1, nspec
    14331436             CALL pmc_set_dataarray_name( 'parent', 'chem_' // TRIM( chem_species(n)%name ),        &
     
    25462549!
    25472550!-- Chemistry, depends on number of species
    2548     IF ( air_chemistry  .AND.  nest_chemistry )  pmc_max_array = pmc_max_array + nspec
     2551    IF ( air_chemistry )  pmc_max_array = pmc_max_array + nspec
    25492552!
    25502553!-- SALSA, depens on the number aerosol size bins and chemical components +
     
    26232626    IF ( TRIM(name) == "s"    )  p_3d_sec => s_2
    26242627    IF ( TRIM(name) == "diss" )  p_3d_sec => diss_2
    2625     IF ( INDEX( TRIM(name), "chem_" ) /= 0      )  p_3d_sec => spec_conc_2(:,:,:,n)
    2626     IF ( INDEX( TRIM(name), "an_" ) /= 0 )  p_3d_sec => nconc_2(:,:,:,n)
    2627     IF ( INDEX( TRIM(name), "am_" ) /= 0 )  p_3d_sec => mconc_2(:,:,:,n)
    2628     IF ( INDEX( TRIM(name), "sg_" ) /= 0  .AND.  .NOT. salsa_gases_from_chem ) &
    2629        p_3d_sec => gconc_2(:,:,:,n)
     2628    IF ( INDEX( TRIM(name), "chem_" ) /= 0 )  p_3d_sec => spec_conc_2(:,:,:,n)
     2629    IF ( INDEX( TRIM(name), "an_" )   /= 0 )  p_3d_sec => nconc_2(:,:,:,n)
     2630    IF ( INDEX( TRIM(name), "am_" )   /= 0 )  p_3d_sec => mconc_2(:,:,:,n)
     2631    IF ( INDEX( TRIM(name), "sg_" )   /= 0  .AND.  .NOT. salsa_gases_from_chem ) &
     2632                                 p_3d_sec => gconc_2(:,:,:,n)
    26302633
    26312634    IF ( ASSOCIATED( p_3d ) )  THEN
     
    29532956       ENDIF
    29542957
    2955        IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     2958       IF ( air_chemistry )  THEN
    29562959          DO  n = 1, nspec
    29572960             CALL pmci_interp_1sto_all ( chem_species(n)%conc, chem_spec_c(:,:,:,n),                &
     
    36303633             ENDIF
    36313634
    3632              IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     3635             IF ( air_chemistry )  THEN
    36333636                DO  n = 1, nspec
    36343637                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    37013704             ENDIF
    37023705
    3703              IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     3706             IF ( air_chemistry )  THEN
    37043707                DO  n = 1, nspec
    37053708                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    37723775             ENDIF
    37733776
    3774              IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     3777             IF ( air_chemistry )  THEN
    37753778                DO  n = 1, nspec
    37763779                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    38433846             ENDIF
    38443847
    3845              IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     3848             IF ( air_chemistry )  THEN
    38463849                DO  n = 1, nspec
    38473850                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    39093912       ENDIF
    39103913
    3911        IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     3914       IF ( air_chemistry )  THEN
    39123915          DO  n = 1, nspec
    39133916             CALL pmci_interp_1sto_t( chem_species(n)%conc, chem_spec_c(:,:,:,n),                   &
     
    40004003      ENDIF
    40014004
    4002       IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     4005      IF ( air_chemistry )  THEN
    40034006         DO  n = 1, nspec
    40044007            CALL pmci_anterp_tophat( chem_species(n)%conc, chem_spec_c(:,:,:,n),                    &
     
    50525055!
    50535056!-- Set Neumann boundary conditions for chemical species
    5054     IF ( air_chemistry  .AND.  nest_chemistry )  THEN
     5057    IF ( air_chemistry )  THEN
    50555058       IF ( ibc_cs_b == 1 )  THEN
    50565059          DO  n = 1, nspec
  • palm/trunk/SOURCE/surface_data_output_mod.f90

    r3881 r4029  
    2525! -----------------
    2626! $Id$
     27! netcdf variable NF90_NOFILL is used as argument instead of "1" in call to NF90_DEF_VAR_FILL
     28!
     29! 3881 2019-04-10 09:31:22Z suehring
    2730! Check for zero output timestep (not allowed in parallel NetCDF output mode)
    2831!
     
    13021305                nc_stat = NF90_DEF_VAR_FILL( id_set_surf(av),                  &
    13031306                                             id_var_dosurf(av,i),              &
    1304                                              1, 0 )
     1307                                             NF90_NOFILL, 0 )
    13051308                CALL netcdf_handle_error( 'surface_data_output_init', 5566 )
    13061309!
  • palm/trunk/SOURCE/time_integration.f90

    r4022 r4029  
    2525! -----------------
    2626! $Id$
     27! exchange of ghost points and boundary conditions separated for chemical species and SALSA module,
     28! bugfix: decycling of chemistry species after nesting data transfer
     29!
     30! 4022 2019-06-12 11:52:39Z suehring
    2731! Call synthetic turbulence generator at last RK3 substep right after boundary
    2832! conditions are updated in offline nesting in order to assure that
     
    10681072             DO  lsp = 1, nvar
    10691073                CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
    1070 !
    1071 !--             kanani: Push chem_boundary_conds after CALL boundary_conds
     1074             ENDDO
     1075          ENDIF
     1076
     1077          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     1078             DO  ib = 1, nbins_aerosol
     1079                CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
     1080                DO  ic = 1, ncomponents_mass
     1081                   icc = ( ic - 1 ) * nbins_aerosol + ib
     1082                   CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
     1083                ENDDO
     1084             ENDDO
     1085             IF ( .NOT. salsa_gases_from_chem )  THEN
     1086                DO  ig = 1, ngases_salsa
     1087                   CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
     1088                ENDDO
     1089             ENDIF
     1090          ENDIF
     1091          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
     1092
     1093!
     1094!--       Boundary conditions for the prognostic quantities (except of the
     1095!--       velocities at the outflow in case of a non-cyclic lateral wall)
     1096          CALL boundary_conds
     1097
     1098!
     1099!--       Boundary conditions for prognostic quantitites of other modules:
     1100!--       Here, only decycling is carried out
     1101          IF ( air_chemistry )  THEN
     1102
     1103             DO  lsp = 1, nvar
    10721104                lsp_usr = 1
    10731105                DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    1074                    IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     1106                   IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
    10751107                      CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    10761108                                                chem_species(lsp)%conc_pr_init )
     
    10791111                ENDDO
    10801112             ENDDO
     1113
    10811114          ENDIF
    10821115
    10831116          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    1084 !
    1085 !--          Exchange ghost points and decycle boundary concentrations if needed
     1117
    10861118             DO  ib = 1, nbins_aerosol
    1087                 CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
    10881119                CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
    10891120                DO  ic = 1, ncomponents_mass
    10901121                   icc = ( ic - 1 ) * nbins_aerosol + ib
    1091                    CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
    10921122                   CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
    10931123                ENDDO
     
    10951125             IF ( .NOT. salsa_gases_from_chem )  THEN
    10961126                DO  ig = 1, ngases_salsa
    1097                    CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
    10981127                   CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
    10991128                ENDDO
    11001129             ENDIF
    1101           ENDIF
    1102           CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    1103 
    1104 !
    1105 !--       Boundary conditions for the prognostic quantities (except of the
    1106 !--       velocities at the outflow in case of a non-cyclic lateral wall)
    1107           CALL boundary_conds
     1130
     1131          ENDIF
     1132
    11081133!
    11091134!--       Swap the time levels in preparation for the next time step.
     
    11301155
    11311156             IF ( TRIM( nesting_mode ) == 'two-way' .OR.  nesting_mode == 'vertical' )  THEN
     1157
     1158                CALL cpu_log( log_point_s(92), 'exchange-horiz-nest', 'start' )
    11321159!
    11331160!--             Exchange_horiz is needed for all parent-domains after the
     
    11701197                   DO  ib = 1, nbins_aerosol
    11711198                      CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
    1172                       CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
    11731199                      DO  ic = 1, ncomponents_mass
    11741200                         icc = ( ic - 1 ) * nbins_aerosol + ib
    11751201                         CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
    1176                          CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
    11771202                      ENDDO
    11781203                   ENDDO
     
    11801205                      DO  ig = 1, ngases_salsa
    11811206                         CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
    1182                          CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
    11831207                      ENDDO
    11841208                   ENDIF
    11851209                ENDIF
    1186                 CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    1187 
    1188              ENDIF
     1210                CALL cpu_log( log_point_s(92), 'exchange-horiz-nest', 'stop' )
     1211
     1212             ENDIF
     1213
    11891214!
    11901215!--          Set boundary conditions again after interpolation and anterpolation.
    11911216             CALL pmci_boundary_conds
     1217
     1218!
     1219!--          Set chemistry boundary conditions (decycling)
     1220             IF ( air_chemistry )  THEN
     1221                DO  lsp = 1, nvar
     1222                   lsp_usr = 1
     1223                   DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     1224                      IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
     1225                         CALL chem_boundary_conds( chem_species(lsp)%conc,                         &
     1226                                                   chem_species(lsp)%conc_pr_init )
     1227                      ENDIF
     1228                      lsp_usr = lsp_usr + 1
     1229                   ENDDO
     1230                ENDDO
     1231             ENDIF
     1232
     1233!
     1234!--          Set SALSA boundary conditions (decycling)
     1235             IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
     1236                DO  ib = 1, nbins_aerosol
     1237                   CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
     1238                   DO  ic = 1, ncomponents_mass
     1239                      icc = ( ic - 1 ) * nbins_aerosol + ib
     1240                      CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
     1241                   ENDDO
     1242                ENDDO
     1243                IF ( .NOT. salsa_gases_from_chem )  THEN
     1244                   DO  ig = 1, ngases_salsa
     1245                      CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
     1246                   ENDDO
     1247                ENDIF
     1248             ENDIF
    11921249
    11931250             CALL cpu_log( log_point(60), 'nesting', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.