Changeset 3241 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- Sep 12, 2018 3:02:00 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r3215 r3241 298 298 299 299 USE control_parameters, & 300 ONLY: air_chemistry, bc_radiation_l, bc_radiation_n, bc_radiation_r, &301 bc_radiation_s 300 ONLY: bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s 301 302 302 USE indices, & 303 ONLY: nxl, nxr, nxlg, nxrg, nyng, nysg, nzt303 ONLY: nxl, nxr, nzt 304 304 305 ! USE prognostic_equations_mod, &306 307 305 USE arrays_3d, & 308 306 ONLY: dzu 307 309 308 USE surface_mod, & 310 309 ONLY: bc_h … … 318 317 INTEGER(iwp) :: m !< running index surface elements. 319 318 INTEGER(iwp) :: lsp !< running index for chem spcs. 320 INTEGER(iwp) :: lph !< running index for photolysis frequencies321 319 322 320 … … 469 467 INTEGER :: lsp_pr !< running index for number of species in cs_names, cs_profiles etc 470 468 INTEGER :: lpr_lev !< running index for profile level for each chem spcs. 471 INTEGER :: npr_lev !< the next available profile lev469 ! INTEGER :: npr_lev !< the next available profile lev 472 470 473 471 !----------------- … … 548 546 !------------------------------------------------------------------------------! 549 547 SUBROUTINE chem_init 550 551 552 USE control_parameters, &553 ONLY: message_string, io_blocks, io_group, turbulent_inflow554 555 USE arrays_3d, &556 ONLY: mean_inflow_profiles557 548 558 549 USE pegrid … … 917 908 INTEGER(iwp) :: lsp !< running index for chem spcs. 918 909 INTEGER(iwp) :: lph !< running index for photolysis frequencies 919 INTEGER :: k,m,istatf910 INTEGER :: istatf 920 911 INTEGER,dimension(20) :: istatus 921 912 REAL(kind=wp),dimension(nzb+1:nzt,nspec) :: tmp_conc … … 926 917 REAL(wp) :: conv !< conversion factor 927 918 REAL(wp), PARAMETER :: ppm2fr = 1.0e-6_wp !< Conversion factor ppm to fraction 928 REAL(wp), PARAMETER :: pref_i = 1._wp / 100000.0_wp !< inverse reference pressure (1/Pa)929 919 REAL(wp), PARAMETER :: t_std = 273.15_wp !< standard pressure (Pa) 930 920 REAL(wp), PARAMETER :: p_std = 101325.0_wp !< standard pressure (Pa) 931 REAL(wp), PARAMETER :: r_cp = 0.286_wp !< R / cp (exponent for potential temperature)932 921 REAL(wp), PARAMETER :: vmolcm = 22.414e3_wp !< Mole volume (22.414 l) in cm^{-3} 933 922 REAL(wp), PARAMETER :: xna = 6.022e23_wp !< Avogadro number (molecules/mol) … … 1068 1057 SUBROUTINE chem_check_data_output( var, unit, i, ilen, k ) 1069 1058 1070 1071 USE control_parameters, &1072 ONLY: data_output, message_string1073 1074 1059 IMPLICIT NONE 1075 1060 … … 1077 1062 CHARACTER (LEN=*) :: var !< 1078 1063 1079 INTEGER(iwp) :: i, lsp 1080 INTEGER(iwp) :: ilen 1081 INTEGER(iwp) :: k 1064 INTEGER(iwp) :: i, ilen, k, lsp 1082 1065 1083 1066 CHARACTER(len=16) :: spec_name … … 1278 1261 INTEGER(iwp) :: m !< running index surface type 1279 1262 INTEGER(iwp) :: lsp !< running index for chem spcs 1280 INTEGER(iwp) :: lsp_2 !< it looks like redundent .. will be delted ..bK1281 1263 1282 1264 IF ( mode == 'allocate' ) THEN 1283 1265 DO lsp = 1, nspec 1284 1266 IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN 1285 ! lsp_2 = lsp1286 1267 chem_species(lsp)%conc_av = 0.0_wp 1287 1288 1268 ENDIF 1289 1269 ENDDO … … 1293 1273 DO lsp = 1, nspec 1294 1274 IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN 1295 ! lsp_2 = lsp1296 1275 DO i = nxlg, nxrg 1297 1276 DO j = nysg, nyng … … 1336 1315 DO lsp = 1, nspec 1337 1316 IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN 1338 ! lsp_2 = lsp1339 1317 DO i = nxlg, nxrg 1340 1318 DO j = nysg, nyng
Note: See TracChangeset
for help on using the changeset viewer.