Changeset 3787 for palm/trunk/SOURCE/salsa_mod.f90
- Timestamp:
- Mar 7, 2019 8:43:54 AM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/salsa_mod.f90
r3780 r3787 26 26 ! ----------------- 27 27 ! $Id$ 28 ! unused variables removed 29 ! 30 ! 3780 2019-03-05 11:19:45Z forkel 28 31 ! unused variable for file index removed from rrd-subroutines parameter list 29 32 ! … … 297 300 !< if particle water is advected) 298 301 REAL(wp) :: act_coeff = 1.0E-7_wp !< Activation coefficient 299 REAL(wp) :: aerosol_source = 0.0_wp !< Constant aerosol flux (#/(m3*s))300 302 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: emission_mass_fracs !< array for 301 303 !< aerosol composition per emission category … … 2042 2044 IMPLICIT NONE 2043 2045 2044 CHARACTER (LEN=20) :: field_char !<2045 2046 INTEGER(iwp) :: b !< 2046 2047 INTEGER(iwp) :: c !< … … 3111 3112 3112 3113 INTEGER(iwp) :: b !< loop index 3113 INTEGER(iwp) :: c !< loop index3114 3114 REAL(wp) :: avis !< molecular viscocity of air (kg/(m*s)) 3115 3115 REAL(wp), PARAMETER :: c_A = 1.249_wp !< Constants A, B and C for … … 3197 3197 3198 3198 INTEGER(iwp) :: c !< loop index 3199 REAL(wp), PARAMETER :: c_A = 1.249_wp !< Constants A, B and C for 3200 REAL(wp), PARAMETER :: c_B = 0.42_wp !< calculating the Cunningham 3201 REAL(wp), PARAMETER :: c_C = 0.87_wp !< slip-flow correction (Cc) 3202 !< according to Jacobson (2005), 3203 !< Eq. 15.30 3199 3204 3200 REAL(wp) :: alpha !< parameter, Table 3 in Zhang et al. (2001) 3205 3201 REAL(wp) :: depo !< deposition efficiency … … 3450 3446 REAL(wp), INTENT(in) :: visc !< molecular viscosity of air (kg/(m*s)) 3451 3447 3452 REAL(wp), PARAMETER :: rhoa_ref = 1.225_wp ! reference air density (kg/m3)3453 3448 ! 3454 3449 !-- Stokes law with Cunningham slip correction factor … … 5571 5566 REAL(wp) :: zcgnh3eqae(nbins) !< Equilibrium gas concentration: NH3 5572 5567 REAL(wp) :: zcgno3eqae(nbins) !< Equilibrium gas concentration: HNO3 5573 REAL(wp) :: zcgwaeqae(nbins) !< Equilibrium gas concentration: H2O5574 5568 REAL(wp) :: zcnh3c !< Current NH3 gas concentration 5575 5569 REAL(wp) :: zcnh3int !< Intermediate NH3 gas concentration … … 5670 5664 ! 5671 5665 !-- NH4/HNO3 saturation ratios for aerosols 5672 CALL SVsat( ptemp, paero, zacno3ae, zacnh3ae, zacnh4hso2ae, zachhso4ae, & 5673 zcgno3eqae, zcno3cae, zcnh3cae, zkelno3ae, zkelnh3ae, & 5674 zsathno3ae, zsatnh3ae, zmolsae ) 5666 CALL SVsat( ptemp, paero, zacno3ae, zacnh4hso2ae, zachhso4ae, zcgno3eqae, & 5667 zcno3cae, zcnh3cae, zkelno3ae, zkelnh3ae, zsathno3ae, zsatnh3ae ) 5675 5668 ! 5676 5669 !-- Intermediate concentrations … … 5808 5801 !> Calculate saturation ratios of NH4 and HNO3 for aerosols 5809 5802 !------------------------------------------------------------------------------! 5810 SUBROUTINE SVsat( ptemp, ppart, pachno3, pacnh3, pacnh4hso2, pachhso4, & 5811 pchno3eq, pchno3, pcnh3, pkelhno3, pkelnh3, psathno3, & 5812 psatnh3, pmols ) 5803 SUBROUTINE SVsat( ptemp, ppart, pachno3, pacnh4hso2, pachhso4, pchno3eq, & 5804 pchno3, pcnh3, pkelhno3, pkelnh3, psathno3, psatnh3 ) 5813 5805 5814 5806 IMPLICIT NONE … … 5819 5811 !-- Activity coefficients 5820 5812 REAL(wp), INTENT(in) :: pachhso4(nbins) !< 5821 REAL(wp), INTENT(in) :: pacnh3(nbins) !<5822 5813 REAL(wp), INTENT(in) :: pacnh4hso2(nbins) !< 5823 5814 REAL(wp), INTENT(in) :: pachno3(nbins) !< … … 5830 5821 REAL(wp), INTENT(in) :: pkelhno3(nbins) !< Kelvin effect for HNO3 5831 5822 REAL(wp), INTENT(in) :: pkelnh3(nbins) !< Kelvin effect for NH3 5832 REAL(wp), INTENT(in) :: pmols(nbins,7)5833 5823 !-- Saturation ratios 5834 5824 REAL(wp), INTENT(out) :: psathno3(nbins) !< … … 7035 7025 SUBROUTINE salsa_diagnostics( i, j ) 7036 7026 7037 USE arrays_3d, &7038 ONLY: p, pt, zu7039 7040 USE basic_constants_and_equations_mod, &7041 ONLY: g7042 7043 USE control_parameters, &7044 ONLY: pt_surface, surface_pressure7045 7046 7027 USE cpulog, & 7047 7028 ONLY: cpu_log, log_point_s … … 7228 7209 ONLY: advec_s_up 7229 7210 USE arrays_3d, & 7230 ONLY: ddzu, hyp, pt,rdf_sc, tend7211 ONLY: ddzu, rdf_sc, tend 7231 7212 USE diffusion_s_mod, & 7232 7213 ONLY: diffusion_s … … 7234 7215 ONLY: wall_flags_0 7235 7216 USE pegrid, & 7236 ONLY: threads_per_task , myid7217 ONLY: threads_per_task 7237 7218 USE surface_mod, & 7238 7219 ONLY : surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, & … … 7912 7893 INTEGER(iwp) :: j !< loop index: y-direction 7913 7894 INTEGER(iwp) :: k !< loop index: z-direction 7914 INTEGER(iwp) :: kg !< loop index: z-direction (gases)7915 7895 INTEGER(iwp) :: n_dt !< number of time steps in the emission file 7916 7896 INTEGER(iwp) :: nc_stat !< local variable for storing the result of … … 7919 7899 INTEGER(iwp) :: ncat !< Number of emission categories 7920 7900 INTEGER(iwp) :: ng_file !< Number of grid-points in file (gases) 7921 INTEGER(iwp) :: num_vars !< number of variables in input file7922 7901 INTEGER(iwp) :: nz_file !< number of grid-points in file 7923 7902 INTEGER(iwp) :: n !< loop index … … 7938 7917 !-- 1 = traffic, 2 = road dust, 3 = wood combustion, 4 = other 7939 7918 !-- Mass fractions: H2SO4, OC, BC, DU, SS, HNO3, NH3 7940 CHARACTER(LEN=15), DIMENSION(ndc) :: cat_name_table = &!< emission category7941 (/'road traffic ','road dust ',&7942 'wood combustion','other '/)7919 ! CHARACTER(LEN=15), DIMENSION(ndc) :: cat_name_table = &!< emission category 7920 ! (/'road traffic ','road dust ',& 7921 ! 'wood combustion','other '/) 7943 7922 REAL(wp), DIMENSION(ndc) :: avg_density !< average density 7944 7923 REAL(wp), DIMENSION(ndc) :: conversion_factor !< unit conversion factor … … 8445 8424 8446 8425 USE arrays_3d, & 8447 ONLY: hyp, pt,rho_air_zw8426 ONLY: rho_air_zw 8448 8427 8449 8428 USE surface_mod, & … … 8455 8434 TYPE(surf_type), INTENT(inout) :: surface !< respective surface type 8456 8435 INTEGER(iwp) :: b !< loop index 8457 INTEGER(iwp) :: ee !< loop index8458 INTEGER(iwp) :: g !< loop index8459 8436 INTEGER(iwp) :: i !< loop index 8460 8437 INTEGER(iwp) :: j !< loop index … … 8463 8440 INTEGER(iwp) :: n !< loop index for emission categories 8464 8441 INTEGER(iwp) :: c !< loop index 8465 INTEGER(iwp) :: ss !< loop index8466 8442 8467 8443 DO m = 1, surface%ns … … 8619 8595 TYPE(surf_type), INTENT(inout) :: surface !< respective surface type 8620 8596 8621 INTEGER(iwp) :: ee !< index: end8622 8597 INTEGER(iwp) :: i !< loop index 8623 8598 INTEGER(iwp) :: j !< loop index 8624 8599 INTEGER(iwp) :: k !< loop index 8625 8600 INTEGER(iwp) :: c !< loop index 8626 INTEGER(iwp) :: ss !<index: start8627 8601 8628 8602 ! … … 9242 9216 REAL(wp), DIMENSION(:,:,:), POINTER :: to_be_resorted !< pointer 9243 9217 9218 ! 9219 !-- Next statement is to avoid compiler warning about unused variable. May be removed in future. 9220 IF ( two_d ) CONTINUE 9244 9221 9245 9222 found = .TRUE.
Note: See TracChangeset
for help on using the changeset viewer.