Changeset 4280 for palm/trunk/SOURCE/salsa_mod.f90
- Timestamp:
- Oct 29, 2019 2:34:15 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/salsa_mod.f90
r4273 r4280 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Corrected a bug in boundary conditions and fac_dt in offline nesting 29 ! 30 ! 4273 2019-10-24 13:40:54Z monakurppa 28 31 ! - Rename nest_salsa to nesting_salsa 29 32 ! - Correct some errors in boundary condition flags … … 217 220 !> 218 221 !> @todo Apply information from emission_stack_height to lift emission sources 219 !> @todo emission mode "parameterized", i.e. based on street type220 222 !> @todo Allow insoluble emissions 221 !> @todo Apply flux limiter in prognostic equations222 223 !------------------------------------------------------------------------------! 223 224 MODULE salsa_mod … … 1121 1122 ! 1122 1123 !-- 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 1124 1131 ! 1125 1132 !-- Set boundary conditions also in case the model is offline-nested in larger-scale models. … … 1177 1184 init_gases_type = 1 1178 1185 ENDIF 1186 1179 1187 1180 1188 END SUBROUTINE salsa_check_parameters … … 8943 8951 aero_emission%mass_fracs(:,cc_i2m(7)) 8944 8952 ! 8945 !-- Allocate and read surface emission data (in total PM )8953 !-- Allocate and read surface emission data (in total PM, get_variable_3d_real) 8946 8954 ALLOCATE( aero_emission%def_data(nys:nyn,nxl:nxr,1:aero_emission_att%ncat) ) 8947 8955 CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%def_data, & … … 9113 9121 source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) ) 9114 9122 ! 9115 !-- Read in the next time step 9123 !-- Read in the next time step (get_variable_4d_to_3d_real) 9116 9124 CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%preproc_data, & 9117 9125 aero_emission_att%tind, 0, aero_emission_att%ncat-1, & … … 12184 12192 !-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed 12185 12193 !-- 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) ) 12189 12198 fac_dt = MIN( 1.0_wp, fac_dt ) 12190 12199
Note: See TracChangeset
for help on using the changeset viewer.