Ignore:
Timestamp:
Oct 29, 2019 2:34:15 PM (5 years ago)
Author:
monakurppa
Message:

Correct recent bugs in salsa_mod and remove chemistry specific stuff in netcdf_data_iput_mod

  • A boundary conditions bug in salsa_mod: set top boundary to its default value (neumann) if nesting is turned off
  • In salsa_nesting_offl_bc, correct fac_dt to apply time_utc_init
  • Remove chemistry specific parts (inside an if clause id==id_emis) in get_variable_4d_to_3d_real and get_variable_5d_to_4d_real
File:
1 edited

Legend:

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

    r4273 r4280  
    2626! -----------------
    2727! $Id$
     28! Corrected a bug in boundary conditions and fac_dt in offline nesting
     29!
     30! 4273 2019-10-24 13:40:54Z monakurppa
    2831! - Rename nest_salsa to nesting_salsa
    2932! - Correct some errors in boundary condition flags
     
    217220!>
    218221!> @todo Apply information from emission_stack_height to lift emission sources
    219 !> @todo emission mode "parameterized", i.e. based on street type
    220222!> @todo Allow insoluble emissions
    221 !> @todo Apply flux limiter in prognostic equations
    222223!------------------------------------------------------------------------------!
    223224 MODULE salsa_mod
     
    11211122!
    11221123!-- For nested runs, explicitly set nesting boundary conditions.
    1123     IF ( nesting_salsa  .AND. child_domain )  bc_salsa_t = 'nested'
     1124    IF ( child_domain )  THEN
     1125       IF ( nesting_salsa )  THEN
     1126          bc_salsa_t = 'nested'
     1127       ELSE
     1128          bc_salsa_t = 'neumann'
     1129       ENDIF
     1130    ENDIF
    11241131!
    11251132!-- Set boundary conditions also in case the model is offline-nested in larger-scale models.
     
    11771184       init_gases_type = 1
    11781185    ENDIF
     1186
    11791187
    11801188 END SUBROUTINE salsa_check_parameters
     
    89438951                                                               aero_emission%mass_fracs(:,cc_i2m(7))
    89448952!
    8945 !--             Allocate and read surface emission data (in total PM)
     8953!--             Allocate and read surface emission data (in total PM, get_variable_3d_real)
    89468954                ALLOCATE( aero_emission%def_data(nys:nyn,nxl:nxr,1:aero_emission_att%ncat) )
    89478955                CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%def_data,    &
     
    91139121                       source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
    91149122!
    9115 !--          Read in the next time step
     9123!--          Read in the next time step (get_variable_4d_to_3d_real)
    91169124             CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%preproc_data,   &
    91179125                                aero_emission_att%tind, 0, aero_emission_att%ncat-1,               &
     
    1218412192!-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed
    1218512193!-- time(tind_p) before boundary data is updated again.
    12186     fac_dt = ( time_since_reference_point - salsa_nest_offl%time(salsa_nest_offl%tind)  + dt_3d )  &
    12187              / ( salsa_nest_offl%time(salsa_nest_offl%tind_p) -                                    &
    12188                  salsa_nest_offl%time(salsa_nest_offl%tind) )
     12194    fac_dt = ( time_utc_init + time_since_reference_point -                                        &
     12195               salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) /                              &
     12196             ( salsa_nest_offl%time(salsa_nest_offl%tind_p) -                                      &
     12197               salsa_nest_offl%time(salsa_nest_offl%tind) )
    1218912198    fac_dt = MIN( 1.0_wp, fac_dt )
    1219012199
Note: See TracChangeset for help on using the changeset viewer.