Changeset 4577 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- Jun 25, 2020 9:53:58 AM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r4559 r4577 26 26 ! ----------------- 27 27 ! $Id$ 28 ! further re-formatting to follow the PALM coding standard 29 ! 30 ! 4559 2020-06-11 08:51:48Z raasch 28 31 ! file re-formatted to follow the PALM coding standard 29 32 ! … … 364 367 REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: spec_conc_3 !< pointer for swapping of timelevels for conc 365 368 REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: freq_1 !< pointer for phtolysis frequncies 366 !< (only 1 timelevel required) 367 !< (e.g. solver type) 368 369 !< (only 1 timelevel required) (e.g. solver type) 369 370 370 371 ! … … 1567 1568 USE control_parameters 1568 1569 1570 REAL(wp), PARAMETER :: fill_value = -9999.0_wp !< value for the _FillValue attribute 1571 1569 1572 CHARACTER(LEN=16) :: spec_name 1570 1573 CHARACTER(LEN=*) :: variable !< … … 1586 1589 REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) :: local_pf !< 1587 1590 1588 REAL(wp), PARAMETER :: fill_value = -9999.0_wp !< value for the _FillValue attribute1589 1591 1590 1592 ! … … 2279 2281 ONLY: dt_3d, intermediate_timestep_count, time_since_reference_point 2280 2282 2283 REAL(wp), PARAMETER :: fr2ppm = 1.0e6_wp !< Conversion factor fraction to ppm 2284 ! REAL(wp), PARAMETER :: xm_air = 28.96_wp !< Mole mass of dry air 2285 ! REAL(wp), PARAMETER :: xm_h2o = 18.01528_wp !< Mole mass of water vapor 2286 REAL(wp), PARAMETER :: p_std = 101325.0_wp !< standard pressure (Pa) 2287 REAL(wp), PARAMETER :: ppm2fr = 1.0e-6_wp !< Conversion factor ppm to fraction 2288 REAL(wp), PARAMETER :: t_std = 273.15_wp !< standard pressure (Pa) 2289 REAL(wp), PARAMETER :: vmolcm = 22.414e3_wp !< Mole volume (22.414 l) in cm^3 2290 REAL(wp), PARAMETER :: xna = 6.022e23_wp !< Avogadro number (molecules/mol) 2281 2291 2282 2292 INTEGER,INTENT(IN) :: i … … 2294 2304 REAL(wp) :: conv !< conversion factor 2295 2305 REAL(kind=wp) :: dt_chem 2296 2297 REAL(wp), PARAMETER :: fr2ppm = 1.0e6_wp !< Conversion factor2298 !< fraction to ppm2299 ! REAL(wp), PARAMETER :: xm_air = 28.96_wp !< Mole mass of dry air2300 ! REAL(wp), PARAMETER :: xm_h2o = 18.01528_wp !< Mole mass of water vapor2301 REAL(wp), PARAMETER :: p_std = 101325.0_wp !< standard pressure (Pa)2302 REAL(wp), PARAMETER :: ppm2fr = 1.0e-6_wp !< Conversion factor ppm to2303 !< fraction2304 REAL(wp), PARAMETER :: t_std = 273.15_wp !< standard pressure (Pa)2305 REAL(wp), PARAMETER :: vmolcm = 22.414e3_wp !< Mole volume (22.414 l)2306 !< in cm^32307 REAL(wp), PARAMETER :: xna = 6.022e23_wp !< Avogadro number2308 !< (molecules/mol)2309 2306 2310 2307 REAL(wp),DIMENSION(size(rcntrl)) :: rcntrl_local … … 3442 3439 !-- Particle parameters (PM10 (1), PM25 (2)) partsize (diameter in m), rhopart (density in kg/m3), 3443 3440 !-- slipcor (slip correction factor dimensionless, Seinfeld and Pandis 2006, Table 9.3) 3444 LOGICAL :: match_lsm !< flag indicating natural-type surface3445 LOGICAL :: match_usm !< flag indicating urban-type surface3446 3447 3441 REAL(wp), DIMENSION(1:3,1:2), PARAMETER :: particle_pars = RESHAPE( (/ & 3448 3442 8.0e-6_wp, 1.14e3_wp, 1.016_wp, & !< 1 3449 3443 0.7e-6_wp, 1.14e3_wp, 1.082_wp & !< 2 3450 3444 /), (/ 3, 2 /) ) 3445 3446 LOGICAL :: match_lsm !< flag indicating natural-type surface 3447 LOGICAL :: match_usm !< flag indicating urban-type surface 3448 3451 3449 ! 3452 3450 !-- List of names of possible tracers … … 5301 5299 ! 5302 5300 !-- Local variables 5301 REAL(wp), PARAMETER :: dO3 = 0.13e-4 !< diffusion coefficient of ozon (m2/s) 5302 5303 5303 REAL(wp) :: vpd !< vapour pressure deficit (kPa) 5304 5304 5305 REAL(wp), PARAMETER :: dO3 = 0.13e-4 !< diffusion coefficient of ozon (m2/s)5306 5305 ! 5307 5306 !-- Next line is to avoid compiler warning about unused variables … … 5395 5394 ! 5396 5395 !-- Local variables: 5396 REAL(wp), PARAMETER :: p_sealevel = 1.01325e05 !< Pa 5397 5397 5398 REAL(wp) :: bt 5398 5399 REAL(wp) :: f_env … … 5411 5412 REAL(wp) :: sinphi 5412 5413 5413 REAL(wp), PARAMETER :: p_sealevel = 1.01325e05 !< Pa5414 5414 ! 5415 5415 !-- Check whether vegetation is present: … … 6029 6029 ! 6030 6030 !-- const 6031 6032 6031 REAL(wp), PARAMETER :: kappa_stab = 0.35 !< von Karman constant 6033 6032 REAL(wp), PARAMETER :: thk = 0.19e-4 !< thermal diffusivity of dry air 20 C
Note: See TracChangeset
for help on using the changeset viewer.