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/biometeorology_mod.f90

    r4540 r4577  
    2626! -----------------
    2727! $Id$
     28! further re-formatting concerning Fortran parameter variables
     29!
     30! 4540 2020-05-18 15:23:29Z raasch
    2831! file re-formatted to follow the PALM coding standard
    2932!
     
    187190!
    188191!-- Declare all global variables within the module (alphabetical order)
     192    REAL(wp), PARAMETER ::  bio_fill_value = -9999.0_wp  !< set module fill value, replace by global fill value as soon as available
     193    REAL(wp), PARAMETER ::  human_absorb = 0.7_wp  !< SW absorbtivity of a human body (Fanger 1972)
     194    REAL(wp), PARAMETER ::  human_emiss = 0.97_wp  !< LW emissivity of a human body after (Fanger 1972)
     195
    189196    INTEGER(iwp) ::  bio_cell_level     !< cell level biom calculates for
    190197
     
    209216
    210217    REAL(wp)    ::  bio_output_height  !< height output is calculated in m
    211 
    212     REAL(wp), PARAMETER ::  bio_fill_value = -9999.0_wp  !< set module fill value, replace by global fill value as soon as available
    213     REAL(wp), PARAMETER ::  human_absorb = 0.7_wp  !< SW absorbtivity of a human body (Fanger 1972)
    214     REAL(wp), PARAMETER ::  human_emiss = 0.97_wp  !< LW emissivity of a human body after (Fanger 1972)
    215218
    216219    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mrt_av_grid   !< time average mean
     
    22702273!
    22712274!-- Parameters for standard "Klima-Michel"
    2272     REAL(wp), PARAMETER :: actlev = 134.6862_wp  !< Workload by activity per standardized surface
    2273                                                  !< (A_Du)
     2275    REAL(wp), PARAMETER :: actlev = 134.6862_wp  !< Workload by activity per standardized surface (A_Du)
    22742276    REAL(wp), PARAMETER :: eta = 0.0_wp          !< Mechanical work efficiency for walking on flat
    22752277                                                 !< ground (compare to Fanger (1972) pp 24f)
    22762278!
    22772279!-- Type of program variables
     2280    REAL(wp), PARAMETER :: eps = 0.0005  !< Accuracy in clothing insulation (clo) for evaluation the root of Fanger's PMV (pmva=0)
     2281
    22782282    INTEGER(iwp) :: ncount      !< running index
    22792283    INTEGER(iwp) :: nerr_cold   !< error number (cold conditions)
     
    22812285
    22822286    LOGICAL :: sultrieness
    2283 
    2284     REAL(wp), PARAMETER :: eps = 0.0005  !< Accuracy in clothing insulation (clo) for evaluation the
    2285                                          !< root of Fanger's PMV (pmva=0)
    22862287
    22872288    REAL(wp) ::  clon           !< clo for neutral conditions   (clo)
     
    25042505!-- Type of program variables
    25052506    INTEGER(iwp), PARAMETER  ::  max_iteration = 15_iwp       !< max number of iterations
     2507
     2508    REAL(wp),     PARAMETER  ::  guess_0       = -1.11e30_wp  !< initial guess
     2509
    25062510    INTEGER(iwp) ::  j       !< running index
    2507 
    2508     REAL(wp),     PARAMETER  ::  guess_0       = -1.11e30_wp  !< initial guess
    25092511
    25102512    REAL(wp) ::  clo_lower   !< lower limit of clothing insulation      (clo)
     
    27882790    REAL(wp) ::  dtmrt        !< difference mean radiation to air temperature
    27892791    REAL(wp) ::  pa           !< vapor pressure (hPa) with hard bounds
    2790     REAL(wp) ::  pa_p50       !< ratio actual water vapour pressure to that of relative humidity of 
     2792    REAL(wp) ::  pa_p50       !< ratio actual water vapour pressure to that of relative humidity of
    27912793                              !< 50 %
    27922794    REAL(wp) ::  pmv          !< temp storage og predicted mean vote
     
    29732975!
    29742976!-- Additional output variables of argument list:
    2975     REAL(wp), INTENT ( OUT ) ::  dperctm    !< Mean deviation perct (classical gt) to gt* (rational 
     2977    REAL(wp), INTENT ( OUT ) ::  dperctm    !< Mean deviation perct (classical gt) to gt* (rational
    29762978                                            !< gt calculated based on Gagge's rational PMV*)
    29772979    REAL(wp), INTENT ( OUT ) ::  dperctstd  !< dperctm plus its standard deviation times a factor
     
    30393041!
    30403042!-- Type of output argument
    3041     INTEGER(iwp), INTENT ( OUT ) ::  nerr !< Error indicator: 0 = o.k., +1 = denominator for 
     3043    INTEGER(iwp), INTENT ( OUT ) ::  nerr !< Error indicator: 0 = o.k., +1 = denominator for
    30423044                                          !< intersection = 0
    30433045
    3044     REAL(wp),     INTENT ( OUT ) ::  dpmv_cold_res    !< Increment to adjust pmva according to the 
     3046    REAL(wp),     INTENT ( OUT ) ::  dpmv_cold_res    !< Increment to adjust pmva according to the
    30453047                                                      !< results of Gagge's 2 node model depending on the input
    30463048!
     
    33443346!
    33453347!-- Internal variables
     3348    REAL(wp), PARAMETER :: eps = 0.0005_wp
     3349    REAL(wp), PARAMETER :: eta = 0.0_wp
     3350
    33463351    INTEGER(iwp) ::  ncount
    33473352    INTEGER(iwp) ::  nerr_cold
     
    33493354
    33503355    LOGICAL ::  sultrieness
    3351 
    3352     REAL(wp), PARAMETER :: eps = 0.0005_wp
    3353     REAL(wp), PARAMETER :: eta = 0.0_wp
    33543356
    33553357!    REAL(wp) ::  acti
     
    36393641!
    36403642!-- Internal variables
     3643    REAL(wp), PARAMETER  ::  time_equil = 7200.0_wp
     3644
    36413645    INTEGER(iwp) :: i         !< running index
    36423646    INTEGER(iwp) ::  niter    !< Running index
    3643 
    3644     REAL(wp), PARAMETER  ::  time_equil = 7200.0_wp
    36453647
    36463648    REAL(wp) ::  adjustrate        !< Max storage adjustment rate
     
    36613663    REAL(wp) ::  ws                !< wind speed                             (m/s)
    36623664    REAL(wp) ::  z1                !< Empiric factor for the adaption of the heat
    3663                                    !< ballance equation to the psycho-physical scale 
     3665                                   !< ballance equation to the psycho-physical scale
    36643666                                   !< (Equ. 40 in FANGER)
    36653667    REAL(wp) ::  z2                !< Water vapour diffution through the skin
     
    40874089          IF ( eswdif <= 0.0_wp )  esw = eswpot     !< Limit is evaporation
    40884090          IF ( eswdif > 0.0_wp )   esw = eswphy     !< Limit is sweat production
    4089           IF ( esw  > 0.0_wp )     esw = 0.0_wp     !< Sweat can't be evaporated, no more cooling 
     4091          IF ( esw  > 0.0_wp )     esw = 0.0_wp     !< Sweat can't be evaporated, no more cooling
    40904092                                                    !< effect
    40914093!
Note: See TracChangeset for help on using the changeset viewer.