!> @file chem_modules.f90 !--------------------------------------------------------------------------------------------------! ! This file is part of the PALM model system. ! ! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General ! Public License as published by the Free Software Foundation, either version 3 of the License, or ! (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the ! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General ! Public License for more details. ! ! You should have received a copy of the GNU General Public License along with PALM. If not, see ! . ! ! Copyright 2018-2021 Leibniz Universitaet Hannover ! Copyright 2018-2021 Karlsruhe Institute of Technology ! Copyright 2018-2021 Freie Universitaet Berlin !--------------------------------------------------------------------------------------------------! ! ! Authors: ! -------- ! @author Farah Kanani-Suehring ! @author Basit Khan ! @author Sabine Banzhaf ! @author Emmanuele Russo ! @author Edward C. Chan ! !--------------------------------------------------------------------------------------------------! ! Description: ! ------------ !> Definition of global PALM-4U chemistry variables !--------------------------------------------------------------------------------------------------! ! MODULE chem_modules USE kinds IMPLICIT NONE REAL, PARAMETER :: xm_air = 28.964e-3 !< air molecular weight (kg/mol) REAL, PARAMETER :: xm_C = 12.01115e-3 !< C molecular weight (kg/mol) REAL, PARAMETER :: xm_Ca = 40.07800e-3 !< Ca molecular weight (kg/mol) REAL, PARAMETER :: xm_Cd = 112.41000e-3 !< Cd molecular weight (kg/mol) REAL, PARAMETER :: xm_Cl = 35.45300e-3 !< Cl molecular weight (kg/mol) REAL, PARAMETER :: xm_dummy = 1000.0e-3 !< dummy molecular weight (kg/mol) REAL, PARAMETER :: xm_F = 18.99840e-3 !< F molecular weight (kg/mol) REAL, PARAMETER :: xm_H = 1.00790e-3 !< H molecular weight (kg/mol) REAL, PARAMETER :: xm_K = 39.09800e-3 !< K molecular weight (kg/mol) REAL, PARAMETER :: xm_Mg = 24.30500e-3 !< Mg molecular weight (kg/mol) REAL, PARAMETER :: xm_N = 14.00670e-3 !< N molecular weight (kg/mol) REAL, PARAMETER :: xm_Na = 22.98977e-3 !< Na molecular weight (kg/mol) REAL, PARAMETER :: xm_O = 15.99940e-3 !< O molecular weight (kg/mol) REAL, PARAMETER :: xm_Pb = 207.20000e-3 !< Pb molecular weight (kg/mol) REAL, PARAMETER :: xm_Pb210 = 210.00000e-3 !< Pb (210) molecular weight (kg/mol) REAL, PARAMETER :: xm_Rn222 = 222.00000e-3 !< Rn (222) molecular weight (kg/mol) REAL, PARAMETER :: xm_S = 32.06400e-3 !< S molecular weight (kg/mol) REAL, PARAMETER :: xm_CO2 = xm_C + xm_O * 2 !< CO2 molecular weight (kg/mol) REAL, PARAMETER :: xm_h2o = xm_H * 2 + xm_O !< H2O molecular weight (kg/mol) REAL, PARAMETER :: xm_HNO3 = xm_H + xm_N + xm_O * 3 !< HNO3 molecular weight (kg/mol) REAL, PARAMETER :: xm_o3 = xm_O * 3 !< O3 molecular weight (kg/mol) REAL, PARAMETER :: xm_N2O5 = xm_N * 2 + xm_O * 5 !< N2O5 molecular weight (kg/mol) REAL, PARAMETER :: xm_NH4 = xm_N + xm_H * 4 !< NH4 molecular weight (kg/mol) REAL, PARAMETER :: xm_NO3 = xm_N + xm_O * 3 !< NO3 molecular weight (kg/mol) REAL, PARAMETER :: xm_SO4 = xm_S + xm_O * 4 !< SO4 molecular weight (kg/mol) CHARACTER (LEN=20) :: bc_cs_b = 'dirichlet' !< namelist parameter: surface !< boundary condition for concentration CHARACTER (LEN=20) :: bc_cs_l = 'undefined' !< left boundary condition CHARACTER (LEN=20) :: bc_cs_n = 'undefined' !< north boundary condition CHARACTER (LEN=20) :: bc_cs_r = 'undefined' !< right boundary condition CHARACTER (LEN=20) :: bc_cs_s = 'undefined' !< south boundary condition CHARACTER (LEN=20) :: bc_cs_t = 'initial_gradient' !< namelist parameter: top boudary !< condition for concentration CHARACTER (LEN=30) :: chem_mechanism = 'phstatp' !< namelist parameter: chemistry !< mechanism CHARACTER (LEN=80) :: daytype_mdh = 'workday' !< namelist parameter: type of day !< - workday, weekend, holiday CHARACTER (LEN=80) :: mode_emis = 'PARAMETERIZED' !< namelist parameter: mode of !< chemistry emissions - !< DEFAULT, EXPERT, PARAMETERIZED CHARACTER (LEN=10) :: photolysis_scheme !< 'constant', !< 'simple' (Simple parameterisation from MCM, !< Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180 !< 'fastj' (Wild et al., 2000, J. Atmos. Chem., 37, 245-282) !< STILL NOT IMPLEMENTED CHARACTER (LEN=80) :: time_fac_type = 'MDH' !< namelist parameter: type of time treatment in the mode_emis !< DEFAULT - HOUR, MDH CHARACTER (LEN=11), DIMENSION(99) :: cs_name = 'novalue' !< namelist parameter: !