Ignore:
Timestamp:
Jun 25, 2020 9:53:58 AM (4 years ago)
Author:
raasch
Message:

further re-formatting to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4559 r4577  
    2626! -----------------
    2727! $Id$
     28! further re-formatting to follow the PALM coding standard
     29!
     30! 4559 2020-06-11 08:51:48Z raasch
    2831! file re-formatted to follow the PALM coding standard
    2932!
     
    364367    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_3  !< pointer for swapping of timelevels for conc
    365368    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)
    369370
    370371!
     
    15671568    USE control_parameters
    15681569
     1570    REAL(wp), PARAMETER ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
     1571
    15691572    CHARACTER(LEN=16) ::  spec_name
    15701573    CHARACTER(LEN=*)  ::  variable    !<
     
    15861589    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf   !<
    15871590
    1588     REAL(wp), PARAMETER ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
    15891591
    15901592!
     
    22792281        ONLY:  dt_3d, intermediate_timestep_count, time_since_reference_point
    22802282
     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)
    22812291
    22822292    INTEGER,INTENT(IN)       :: i
     
    22942304    REAL(wp)                         ::  conv                                !< conversion factor
    22952305    REAL(kind=wp)                    ::  dt_chem
    2296 
    2297     REAL(wp), PARAMETER              ::  fr2ppm  = 1.0e6_wp              !< Conversion factor
    2298                                                                          !< fraction to ppm
    2299 !    REAL(wp), PARAMETER              ::  xm_air  = 28.96_wp              !< Mole mass of dry air
    2300 !    REAL(wp), PARAMETER              ::  xm_h2o  = 18.01528_wp           !< Mole mass of water vapor
    2301     REAL(wp), PARAMETER              ::  p_std   = 101325.0_wp           !< standard pressure (Pa)
    2302     REAL(wp), PARAMETER              ::  ppm2fr  = 1.0e-6_wp             !< Conversion factor ppm to
    2303                                                                          !< fraction
    2304     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^3
    2307     REAL(wp), PARAMETER              ::  xna     = 6.022e23_wp           !< Avogadro number
    2308                                                                          !< (molecules/mol)
    23092306
    23102307    REAL(wp),DIMENSION(size(rcntrl)) :: rcntrl_local
     
    34423439!-- Particle parameters (PM10 (1), PM25 (2)) partsize (diameter in m), rhopart (density in kg/m3),
    34433440!-- slipcor (slip correction factor dimensionless, Seinfeld and Pandis 2006, Table 9.3)
    3444     LOGICAL ::  match_lsm     !< flag indicating natural-type surface
    3445     LOGICAL ::  match_usm     !< flag indicating urban-type surface
    3446 
    34473441    REAL(wp), DIMENSION(1:3,1:2), PARAMETER ::  particle_pars = RESHAPE( (/                        &
    34483442                                                         8.0e-6_wp, 1.14e3_wp, 1.016_wp, &   !<  1
    34493443                                                         0.7e-6_wp, 1.14e3_wp, 1.082_wp  &   !<  2
    34503444                                                         /), (/ 3, 2 /) )
     3445
     3446    LOGICAL ::  match_lsm     !< flag indicating natural-type surface
     3447    LOGICAL ::  match_usm     !< flag indicating urban-type surface
     3448
    34513449!
    34523450!-- List of names of possible tracers
     
    53015299!
    53025300!-- Local variables
     5301    REAL(wp), PARAMETER ::  dO3 = 0.13e-4          !< diffusion coefficient of ozon (m2/s)
     5302
    53035303    REAL(wp) ::  vpd                               !< vapour pressure deficit (kPa)
    53045304
    5305     REAL(wp), PARAMETER ::  dO3 = 0.13e-4          !< diffusion coefficient of ozon (m2/s)
    53065305!
    53075306!-- Next line is to avoid compiler warning about unused variables
     
    53955394!
    53965395!-- Local variables:
     5396    REAL(wp), PARAMETER ::  p_sealevel = 1.01325e05    !< Pa
     5397
    53975398    REAL(wp) ::  bt
    53985399    REAL(wp) ::  f_env
     
    54115412    REAL(wp) ::  sinphi
    54125413
    5413     REAL(wp), PARAMETER ::  p_sealevel = 1.01325e05    !< Pa
    54145414!
    54155415!-- Check whether vegetation is present:
     
    60296029!
    60306030!-- const
    6031 
    60326031    REAL(wp), PARAMETER ::  kappa_stab = 0.35     !< von Karman constant
    60336032    REAL(wp), PARAMETER ::  thk = 0.19e-4         !< thermal diffusivity of dry air 20 C
Note: See TracChangeset for help on using the changeset viewer.