Ignore:
Timestamp:
Oct 29, 2018 6:14:31 PM (5 years ago)
Author:
kanani
Message:

Implementation of human thermal indices (from branch biomet_p2 at r3444)

File:
1 edited

Legend:

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

    r3274 r3448  
    2525! -----------------
    2626! $Id$
     27! Adjustment of biometeorology calls,
     28! implement some agent biometeorology
     29!
     30! 3274 2018-09-24 15:42:55Z knoop
    2731! Modularization of all bulk cloud physics code components
    2832!
     
    8488
    8589    USE control_parameters,                                                    &
    86         ONLY:  dt_3d, message_string, time_since_reference_point, dt_write_agent_data
     90        ONLY:  biometeorology, dt_3d, dt_write_agent_data, message_string,     &
     91               time_since_reference_point
    8792
    8893    USE cpulog,                                                                &
     
    206211        REAL(wp)     ::  clo                  !< clothing index
    207212        REAL(wp)     ::  energy_storage       !< energy stored by agent
     213        REAL(wp)     ::  clothing_temp        !< energy stored by agent
     214        REAL(wp)     ::  actlev               !< metabolic + work energy of the person
     215        REAL(wp)     ::  age_years            !< physical age of the person
     216        REAL(wp)     ::  weight               !< total weight of the person (kg)
     217        REAL(wp)     ::  height               !< height of the person (m)
     218        REAL(wp)     ::  work                 !< workload of the agent (W)
     219        INTEGER(iwp) ::  sex                  !< agents gender: 1 = male, 2 = female
    208220        REAL(wp)     ::  force_x              !< force term x-direction
    209221        REAL(wp)     ::  force_y              !< force term y-direction
     
    218230        REAL(wp)     ::  speed_x              !< speed of agent in x
    219231        REAL(wp)     ::  speed_y              !< speed of agent in y
    220         REAL(wp)     ::  thermal_index        !< the dynamic thermal index
     232        REAL(wp)     ::  ipt                  !< instationary thermal index iPT (°C)
    221233        REAL(wp)     ::  windspeed            !< absolute value of windspeed at agent position
    222234        REAL(wp)     ::  x                    !< x-position
     
    329341 SUBROUTINE multi_agent_system
    330342
    331 !     USE htcm_mod,                                                              &
    332 !         ONLY:  htcm_dynamic
     343    USE biometeorology_mod,                                                   &
     344        ONLY:  biom_calc_ipt, biom_determine_input_at
     345
    333346
    334347    IMPLICIT NONE
     
    341354    INTEGER(iwp)       ::  js                 !< counter
    342355    INTEGER(iwp), SAVE ::  mas_count = 0      !< counts the mas-calls
     356    INTEGER(iwp)                :: a     !< agent iterator
     357    !-- local meteorological conditions
     358    REAL(wp)                    :: tmrt  !< mean radiant temperature        (°C)
     359    REAL(wp)                    :: ta    !< air temperature                 (°C)
     360    REAL(wp)                    :: vp    !< vapour pressure                 (hPa)
     361    REAL(wp)                    :: v     !< wind speed    (local level)     (m/s)
     362    REAL(wp)                    :: pair  !< air pressure                    (hPa)
     363
    343364
    344365    LOGICAL       ::  first_loop_stride   !< flag for first loop stride of agent sub-timesteps
     
    502523       deleted_agents = 0
    503524!
    504 !--    to be included here: call of human thermal comfort mod (and UV exposure)
    505 !        DO  i = nxl, nxr
    506 !           DO  j = nys, nyn
    507 !
    508 !              number_of_agents = agt_count(j,i)
    509 ! !
    510 ! !--          If grid cell gets empty, cycle
    511 !              IF ( number_of_agents <= 0 ) CYCLE
    512 !
    513 !              agents => grid_agents(j,i)%agents(1:number_of_agents)
    514 ! !
    515 ! !--          Evaluation of social forces
    516 !              CALL htcm_dynamic(i,j)
    517 !
    518 !           ENDDO
    519 !        ENDDO
     525       IF ( biometeorology )  THEN
     526!
     527!--       Call of human thermal comfort mod (and UV exposure)
     528          DO  i = nxl, nxr
     529             DO  j = nys, nyn
     530
     531                number_of_agents = agt_count(j,i)
     532!
     533!--             If grid cell gets empty, cycle
     534                IF ( number_of_agents <= 0 )  CYCLE
     535
     536                agents => grid_agents(j,i)%agents(1:number_of_agents)
     537!
     538!--             Evaluation of social forces
     539!                CALL biom_dynamic(i,j)
     540!
     541!--             Determine local meteorological conditions
     542                CALL biom_determine_input_at ( .FALSE., i, j, ta, vp, v,      &
     543                                               pair, tmrt )
     544
     545                DO  a = 1, number_of_agents
     546!
     547!--                Calculate instationary thermal indices based on local tmrt
     548
     549                   CALL biom_calc_ipt ( ta, vp, v, pair, tmrt,                &
     550                                        agents(a)%dt_sum,                     &
     551                                        agents(a)%energy_storage,             &
     552                                        agents(a)%clothing_temp,              &
     553                                        agents(a)%clo,                        &
     554                                        agents(a)%actlev,                     &
     555                                        agents(a)%age_years,                  &
     556                                        agents(a)%weight,                     &
     557                                        agents(a)%height,                     &
     558                                        agents(a)%work,                       &
     559                                        agents(a)%sex,                        &
     560                                        agents(a)%ipt )
     561                END DO
     562
     563             ENDDO
     564          ENDDO
     565       ENDIF
    520566
    521567       IF ( dt_3d_reached_mas )  EXIT
     
    799845                         tmp_agent%age_m         = 0.0_wp
    800846                         tmp_agent%dt_sum        = 0.0_wp
    801                          tmp_agent%clo           = 99999.0_wp
     847                         tmp_agent%clo           = -999.0_wp
    802848                         tmp_agent%energy_storage= 0.0_wp
     849                         tmp_agent%ipt           = 99999.0_wp
     850                         tmp_agent%clothing_temp = -999._wp      !< energy stored by agent (W)
     851                         tmp_agent%actlev        = 134.6862_wp   !< metabolic + work energy of the person
     852                         tmp_agent%age_years     = 35._wp        !< physical age of the person
     853                         tmp_agent%weight        = 75._wp        !< total weight of the person (kg)
     854                         tmp_agent%height        = 1.75_wp       !< height of the person (m)
     855                         tmp_agent%work          = 134.6862_wp   !< workload of the agent (W)
     856                         tmp_agent%sex           = 1             !< agents gender: 1 = male, 2 = female
    803857                         tmp_agent%force_x       = 0.0_wp
    804858                         tmp_agent%force_y       = 0.0_wp
     
    812866                         tmp_agent%speed_x       = 0.0_wp
    813867                         tmp_agent%speed_y       = 0.0_wp
    814                          tmp_agent%thermal_index = 99999.0_wp
    815868                         tmp_agent%x             = pos_x
    816869                         tmp_agent%y             = pos_y
     
    31853238          zero_agent%speed_x       = 0.0_wp
    31863239          zero_agent%speed_y       = 0.0_wp
    3187           zero_agent%thermal_index = 0.0_wp
     3240          zero_agent%ipt          = 0.0_wp
    31883241          zero_agent%x             = 0.0_wp
    31893242          zero_agent%y             = 0.0_wp
Note: See TracChangeset for help on using the changeset viewer.