Ignore:
Timestamp:
Oct 30, 2018 6:08:55 PM (5 years ago)
Author:
kanani
Message:

from branch resler@3462: add MRT shaping function (radiation_model_mod), use basic constants (biometeorology_mod), adjust precision to wp (biometeorology_pt_mod)

File:
1 edited

Legend:

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

    r3449 r3464  
    2828! -----------------
    2929! $Id$
     30! From branch resler@3462, pavelkrc:
     31! add MRT shaping function for human
     32!
     33! 3449 2018-10-29 19:36:56Z suehring
    3034! New RTM version 3.0: (Pavel Krc, Jaroslav Resler, ICS, Prague)
    3135!   - Interaction of plant canopy with LW radiation
     
    902906    LOGICAL                                        ::  mrt_skip_roof = .TRUE.             !< do not calculate MRT above roof surfaces
    903907    LOGICAL                                        ::  mrt_include_sw = .TRUE.            !< should MRT calculation include SW radiation as well?
     908    LOGICAL                                        ::  mrt_geom_human = .TRUE.            !< MRT direction weights simulate human body instead of a sphere
    904909    INTEGER(iwp)                                   ::  nrefsteps = 3                      !< number of reflection steps to perform
    905910    REAL(wp), PARAMETER                            ::  ext_coef = 0.6_wp                  !< extinction coefficient (a.k.a. alpha)
     
    11721177!-- Public variables and constants / NEEDS SORTING
    11731178    PUBLIC albedo, albedo_type, decl_1, decl_2, decl_3, dots_rad, dt_radiation,&
    1174            emissivity, force_radiation_call, lat, lon,                         &
     1179           emissivity, force_radiation_call, lat, lon, mrt_geom_human,         &
    11751180           mrt_include_sw, mrt_nlevels, mrtbl, mrtinsw, mrtinlw, nmrtbl,       &
    11761181           rad_net_av, radiation, radiation_scheme, rad_lw_in,                 &
     
    29422947                                  constant_albedo, dt_radiation, emissivity,    &
    29432948                                  lw_radiation, max_raytracing_dist,            &
    2944                                   min_irrf_value, mrt_include_sw, mrt_nlevels,  &
     2949                                  min_irrf_value, mrt_geom_human,               &
     2950                                  mrt_include_sw, mrt_nlevels,                  &
    29452951                                  mrt_skip_roof, net_radiation, nrefsteps,      &
    29462952                                  plant_lw_interact, rad_angular_discretization,&
     
    29572963                                  constant_albedo, dt_radiation, emissivity,    &
    29582964                                  lw_radiation, max_raytracing_dist,            &
    2959                                   min_irrf_value, mrt_include_sw, mrt_nlevels,  &
     2965                                  min_irrf_value, mrt_geom_human,               &
     2966                                  mrt_include_sw, mrt_nlevels,                  &
    29602967                                  mrt_skip_roof, net_radiation, nrefsteps,      &
    29612968                                  plant_lw_interact, rad_angular_discretization,&
     
    65536560           zbdry(:) = (/( zn0+REAL(izn,wp)*zns, izn=0, nzn )/)
    65546561           vffrac0(:) = (COS(zbdry(0:nzn-1)) - COS(zbdry(1:nzn))) / 2._wp / REAL(naz, wp)
     6562           !
     6563           !--Modify direction weights to simulate human body (lower weight for top-down)
     6564           IF ( mrt_geom_human )  THEN
     6565              vffrac0(:) = vffrac0(:) * MAX(0._wp, SIN(zcent(:))*0.88_wp + COS(zcent(:))*0.12_wp)
     6566              vffrac0(:) = vffrac0(:) / (SUM(vffrac0) * REAL(naz, wp))
     6567           ENDIF
    65556568
    65566569           DO  imrt = 1, nmrtbl
Note: See TracChangeset for help on using the changeset viewer.