Changeset 4273 for palm/trunk/SOURCE/salsa_mod.f90
- Timestamp:
- Oct 24, 2019 1:40:54 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/salsa_mod.f90
r4272 r4273 26 26 ! ----------------- 27 27 ! $Id$ 28 ! - Rename nest_salsa to nesting_salsa 29 ! - Correct some errors in boundary condition flags 30 ! - Add a check for not trying to output gas concentrations in salsa if the 31 ! chemistry module is applied 32 ! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE. 33 ! 34 ! 4272 2019-10-23 15:18:57Z schwenkel 28 35 ! Further modularization of boundary conditions: moved boundary conditions to 29 36 ! respective modules … … 454 461 LOGICAL :: include_emission = .FALSE. !< Include or not emissions 455 462 LOGICAL :: feedback_to_palm = .FALSE. !< Allow feedback due to condensation of H2O 456 LOGICAL :: nest _salsa = .FALSE.!< Apply nesting for salsa457 LOGICAL :: nesting_offline_salsa = . FALSE.!< Apply offline nesting for salsa463 LOGICAL :: nesting_salsa = .TRUE. !< Apply nesting for salsa 464 LOGICAL :: nesting_offline_salsa = .TRUE. !< Apply offline nesting for salsa 458 465 LOGICAL :: no_insoluble = .FALSE. !< Exclude insoluble chemical components 459 466 LOGICAL :: read_restart_data_salsa = .FALSE. !< Read restart data for salsa … … 652 659 CHARACTER(LEN=15) :: char_t = 'ls_forcing_top_' !< leading substring at top boundary 653 660 654 CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) :: gas_name = (/' h2so4','hno3 ','nh3 ','ocnv ','ocsv'/)661 CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) :: gas_name = (/'H2SO4','HNO3 ','NH3 ','OCNV ','OCSV '/) 655 662 656 663 CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE :: cc_name !< chemical component name … … 973 980 init_aerosol_type, & 974 981 init_gases_type, & 975 nest _salsa,&982 nesting_salsa, & 976 983 nesting_offline_salsa, & 977 984 salsa_gases_from_chem, & … … 1037 1044 n_lognorm, & 1038 1045 nbin, & 1039 nest _salsa,&1046 nesting_salsa, & 1040 1047 nesting_offline_salsa, & 1041 1048 nf2a, & … … 1102 1109 1103 1110 USE control_parameters, & 1104 ONLY: humidity, initializing_actions1111 ONLY: child_domain, humidity, initializing_actions, nesting_offline 1105 1112 1106 1113 IMPLICIT NONE … … 1111 1118 WRITE( message_string, * ) 'salsa = ', salsa, ' is not allowed with humidity = ', humidity 1112 1119 CALL message( 'salsa_check_parameters', 'PA0594', 1, 2, 0, 6, 0 ) 1120 ENDIF 1121 ! 1122 !-- For nested runs, explicitly set nesting boundary conditions. 1123 IF ( nesting_salsa .AND. child_domain ) bc_salsa_t = 'nested' 1124 ! 1125 !-- Set boundary conditions also in case the model is offline-nested in larger-scale models. 1126 IF ( nesting_offline ) THEN 1127 IF ( nesting_offline_salsa ) THEN 1128 bc_salsa_t = 'nesting_offline' 1129 ELSE 1130 bc_salsa_t = 'neumann' 1131 ENDIF 1113 1132 ENDIF 1114 1133 ! … … 1128 1147 ELSEIF ( bc_salsa_t == 'neumann' ) THEN 1129 1148 ibc_salsa_t = 1 1130 ELSEIF ( bc_salsa_t == ' nested' ) THEN1149 ELSEIF ( bc_salsa_t == 'initial_gradient' ) THEN 1131 1150 ibc_salsa_t = 2 1151 ELSEIF ( bc_salsa_t == 'nested' .OR. bc_salsa_t == 'nesting_offline' ) THEN 1152 ibc_salsa_t = 3 1132 1153 ELSE 1133 1154 message_string = 'unknown boundary condition: bc_salsa_t = "' // TRIM( bc_salsa_t ) // '"' 1134 1155 CALL message( 'salsa_check_parameters', 'PA0596', 1, 2, 0, 6, 0 ) 1135 ENDIF1136 !1137 !-- If nest_salsa = .F., set top boundary to dirichlet1138 IF ( .NOT. nest_salsa .AND. ibc_salsa_t == 2 ) THEN1139 ibc_salsa_t = 01140 bc_salsa_t = 'dirichlet'1141 1156 ENDIF 1142 1157 ! … … 1246 1261 WRITE( io, 19 ) 1247 1262 ENDIF 1248 IF ( nest_salsa ) WRITE( io, 20 ) nest_salsa 1249 WRITE( io, 21 ) salsa_emission_mode 1263 IF ( nesting_salsa ) WRITE( io, 20 ) nesting_salsa 1264 IF ( nesting_offline_salsa ) WRITE( io, 21 ) nesting_offline_salsa 1265 WRITE( io, 22 ) salsa_emission_mode 1250 1266 IF ( salsa_emission_mode == 'uniform' ) THEN 1251 WRITE( io, 2 2) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag, &1267 WRITE( io, 23 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag, & 1252 1268 aerosol_flux_mass_fracs_a 1253 1269 ENDIF 1254 1270 IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp .OR. salsa_emission_mode == 'read_from_file' ) & 1255 1271 THEN 1256 WRITE( io, 2 3)1272 WRITE( io, 24 ) 1257 1273 ENDIF 1258 1274 … … 1297 1313 19 FORMAT (/' Size distribution read from a file.') 1298 1314 20 FORMAT (/' Nesting for salsa variables: ', L1 ) 1299 21 FORMAT (/' Emissions: salsa_emission_mode = ', A ) 1300 22 FORMAT (/' surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', / & 1315 21 FORMAT (/' Offline nesting for salsa variables: ', L1 ) 1316 22 FORMAT (/' Emissions: salsa_emission_mode = ', A ) 1317 23 FORMAT (/' surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', / & 1301 1318 ' aerosol_flux_dpg = ', 7(F7.3), ' (m)', / & 1302 1319 ' aerosol_flux_sigmag = ', 7(F7.2), / & 1303 1320 ' aerosol_mass_fracs_a = ', 7(ES12.4E3) ) 1304 2 3FORMAT (/' (currently all emissions are soluble!)')1321 24 FORMAT (/' (currently all emissions are soluble!)') 1305 1322 1306 1323 END SUBROUTINE salsa_header … … 2209 2226 ! 2210 2227 !-- Read vertical profiles of gases: 2211 CALL get_variable( id_dyn, 'init_atmosphere_ h2so4', salsa_gas(1)%init(nzb+1:nzt) )2212 CALL get_variable( id_dyn, 'init_atmosphere_ hno3', salsa_gas(2)%init(nzb+1:nzt) )2213 CALL get_variable( id_dyn, 'init_atmosphere_ nh3', salsa_gas(3)%init(nzb+1:nzt) )2214 CALL get_variable( id_dyn, 'init_atmosphere_ ocnv', salsa_gas(4)%init(nzb+1:nzt) )2215 CALL get_variable( id_dyn, 'init_atmosphere_ ocsv', salsa_gas(5)%init(nzb+1:nzt) )2228 CALL get_variable( id_dyn, 'init_atmosphere_H2SO4', salsa_gas(1)%init(nzb+1:nzt) ) 2229 CALL get_variable( id_dyn, 'init_atmosphere_HNO3', salsa_gas(2)%init(nzb+1:nzt) ) 2230 CALL get_variable( id_dyn, 'init_atmosphere_NH3', salsa_gas(3)%init(nzb+1:nzt) ) 2231 CALL get_variable( id_dyn, 'init_atmosphere_OCNV', salsa_gas(4)%init(nzb+1:nzt) ) 2232 CALL get_variable( id_dyn, 'init_atmosphere_OCSV', salsa_gas(5)%init(nzb+1:nzt) ) 2216 2233 ! 2217 2234 !-- Set Neumann top and surface boundary condition for initial + initialise concentrations … … 8146 8163 8147 8164 IF ( time_since_reference_point >= skip_time_do_salsa ) THEN 8148 8149 8165 ! 8150 8166 !-- Surface conditions: … … 8247 8263 ENDIF 8248 8264 8249 ELSEIF ( ibc_salsa_t == 2 ) THEN ! nested8265 ELSEIF ( ibc_salsa_t == 2 ) THEN ! Initial gradient 8250 8266 8251 8267 DO ib = 1, nbins_aerosol … … 8358 8374 flag = 0.0_wp 8359 8375 ! 8360 !-- Skip input if forcing from larger-scale models is applied.8376 !-- Skip input if forcing from a larger-scale models is applied. 8361 8377 IF ( nesting_offline .AND. nesting_offline_salsa ) RETURN 8362 8378 ! … … 9778 9794 9779 9795 CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' ) 9780 IF ( salsa_gases_from_chem) THEN9796 IF ( air_chemistry ) THEN 9781 9797 message_string = 'gases are imported from the chemistry module and thus output '// & 9782 9798 'of "' // TRIM( var ) // '" is not allowed'
Note: See TracChangeset
for help on using the changeset viewer.