Ignore:
Timestamp:
Dec 3, 2018 1:51:13 PM (5 years ago)
Author:
kanani
Message:

Bugfix for missing array allocation (biometeorology_mod), remove degree symbol (biometeorology_mod, indoor_model_mod, multi_agent_system_mod, surface_mod, wind_turbine_model_mod)

File:
1 edited

Legend:

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

    r3582 r3593  
    2727! -----------------
    2828! $Id$
     29! Bugfix: additional tmrt_grid allocation in case bio_mrt not selected as ouput,
     30! replace degree symbol by degree_C
     31!
     32! 3582 2018-11-29 19:16:36Z suehring
    2933! Consistently use bio_fill_value everywhere,
    3034! move allocation and initialization of output variables to bio_check_data_output
     
    128132!
    129133!-- Declare all global variables within the module (alphabetical order)
    130     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tmrt_grid  !< tmrt results (°C)
    131     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  perct      !< PT results   (°C)
    132     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  utci       !< UTCI results (°C)
    133     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pet        !< PET results  (°C)
     134    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tmrt_grid  !< tmrt results (degree_C)
     135    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  perct      !< PT results   (degree_C)
     136    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  utci       !< UTCI results (degree_C)
     137    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pet        !< PET results  (degree_C)
    134138!
    135139!-- Grids for averaged thermal indices
    136140    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mrt_av_grid   !< time average mean
    137     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  perct_av      !< PT results (aver. input)   (°C)
    138     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  utci_av       !< UTCI results (aver. input) (°C)
    139     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pet_av        !< PET results (aver. input)  (°C)
     141    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  perct_av      !< PT results (aver. input)   (degree_C)
     142    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  utci_av       !< UTCI results (aver. input) (degree_C)
     143    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pet_av        !< PET results (aver. input)  (degree_C)
    140144
    141145
     
    636640!
    637641!-- Allocate a temporary array with the desired output dimensions.
    638        CASE ( 'bio_mrt')
     642       CASE ( 'bio_mrt' )
    639643          unit = 'degree_C'
    640644          IF ( .NOT. ALLOCATED( tmrt_grid ) )  THEN
     
    11851189
    11861190!
    1187 !-- Calculate biometeorology MRT from local radiation
    1188 !   fluxes calculated by RTM and assign into 2D grid
    1189     tmrt_grid = bio_fill_value
     1191!-- Calculate biometeorology MRT from local radiation fluxes calculated by RTM and assign
     1192!-- into 2D grid. Depending on selected output quantities, tmrt_grid might not have been
     1193!-- allocated in bio_check_data_output yet.
     1194    IF ( .NOT. ALLOCATED( tmrt_grid ) )  THEN
     1195       ALLOCATE( tmrt_grid (nys:nyn,nxl:nxr) )
     1196    ENDIF
     1197    tmrt_grid = REAL( bio_fill_value, KIND = wp )
     1198
    11901199    DO  l = 1, nmrtbl
    11911200       i = mrtbl(ix,l)
     
    12241233!
    12251234!-- Output parameters
    1226     REAL(wp), INTENT ( OUT )    ::  tmrt  !< Mean radiant temperature        (°C)
    1227     REAL(wp), INTENT ( OUT )    ::  ta    !< Air temperature                 (°C)
     1235    REAL(wp), INTENT ( OUT )    ::  tmrt  !< Mean radiant temperature        (degree_C)
     1236    REAL(wp), INTENT ( OUT )    ::  ta    !< Air temperature                 (degree_C)
    12281237    REAL(wp), INTENT ( OUT )    ::  vp    !< Vapour pressure                 (hPa)
    12291238    REAL(wp), INTENT ( OUT )    ::  ws    !< Wind speed    (local level)     (m/s)
     
    13221331
    13231332    REAL(wp) ::  clo          !< Clothing index                (no dimension)
    1324     REAL(wp) ::  ta           !< Air temperature                  (°C)
     1333    REAL(wp) ::  ta           !< Air temperature                  (degree_C)
    13251334    REAL(wp) ::  vp           !< Vapour pressure                  (hPa)
    13261335    REAL(wp) ::  ws           !< Wind speed    (local level)      (m/s)
    13271336    REAL(wp) ::  pair         !< Air pressure                     (hPa)
    1328     REAL(wp) ::  perct_ij     !< Perceived temperature            (°C)
    1329     REAL(wp) ::  utci_ij      !< Universal thermal climate index  (°C)
    1330     REAL(wp) ::  pet_ij       !< Physiologically equivalent temperature  (°C)
    1331     REAL(wp) ::  tmrt_ij      !< Mean radiant temperature         (°C)
     1337    REAL(wp) ::  perct_ij     !< Perceived temperature            (degree_C)
     1338    REAL(wp) ::  utci_ij      !< Universal thermal climate index  (degree_C)
     1339    REAL(wp) ::  pet_ij       !< Physiologically equivalent temperature  (degree_C)
     1340    REAL(wp) ::  tmrt_ij      !< Mean radiant temperature         (degree_C)
    13321341
    13331342!
     
    14231432!
    14241433!-- Input parameters
    1425     REAL(wp), INTENT ( IN )  ::  ta   !< Air temperature                  (°C)
     1434    REAL(wp), INTENT ( IN )  ::  ta   !< Air temperature                  (degree_C)
    14261435    REAL(wp), INTENT ( IN )  ::  vp   !< Vapour pressure                  (hPa)
    14271436    REAL(wp), INTENT ( IN )  ::  ws   !< Wind speed    (local level)      (m/s)
    14281437    REAL(wp), INTENT ( IN )  ::  pair !< Air pressure                     (hPa)
    1429     REAL(wp), INTENT ( IN )  ::  tmrt !< Mean radiant temperature         (°C)
     1438    REAL(wp), INTENT ( IN )  ::  tmrt !< Mean radiant temperature         (degree_C)
    14301439    REAL(wp), INTENT ( IN )  ::  dt   !< Time past since last calculation (s)
    14311440    REAL(wp), INTENT ( IN )  ::  age  !< Age of agent                     (y)
     
    14381447!-- Both, input and output parameters
    14391448    Real(wp), INTENT ( INOUT )  ::  energy_storage    !< Energy storage   (W/m²)
    1440     Real(wp), INTENT ( INOUT )  ::  t_clo   !< Clothing temperature       (°C)
     1449    Real(wp), INTENT ( INOUT )  ::  t_clo   !< Clothing temperature       (degree_C)
    14411450    Real(wp), INTENT ( INOUT )  ::  clo     !< Current clothing in sulation
    14421451    Real(wp), INTENT ( INOUT )  ::  actlev  !< Individuals activity level
     
    14441453!
    14451454!-- Output parameters
    1446     REAL(wp), INTENT ( OUT ) ::  ipt    !< Instationary perceived temp.   (°C)
     1455    REAL(wp), INTENT ( OUT ) ::  ipt    !< Instationary perceived temp.   (degree_C)
    14471456!
    14481457!-- If clo equals the initial value, this is the initial call
     
    14841493!
    14851494!-- Type of input of the argument list
    1486     REAL(WP), INTENT ( IN )  ::  ta_in    !< Local air temperature (°C)
     1495    REAL(WP), INTENT ( IN )  ::  ta_in    !< Local air temperature (degree_C)
    14871496    REAL(WP), INTENT ( IN )  ::  vp       !< Loacl vapour pressure (hPa)
    14881497    REAL(WP), INTENT ( IN )  ::  ws_hag   !< Incident wind speed (m/s)
    1489     REAL(WP), INTENT ( IN )  ::  tmrt     !< Local mean radiant temperature (°C)
     1498    REAL(WP), INTENT ( IN )  ::  tmrt     !< Local mean radiant temperature (degree_C)
    14901499    REAL(WP), INTENT ( IN )  ::  hag      !< Height of wind speed input (m)
    14911500!
    14921501!-- Type of output of the argument list
    1493     REAL(wp), INTENT ( OUT ) ::  utci_ij  !< Universal Thermal Climate Index (°C)
    1494 
    1495     REAL(WP) ::  ta           !< air temperature modified by offset (°C)
     1502    REAL(wp), INTENT ( OUT ) ::  utci_ij  !< Universal Thermal Climate Index (degree_C)
     1503
     1504    REAL(WP) ::  ta           !< air temperature modified by offset (degree_C)
    14961505    REAL(WP) ::  pa           !< air pressure in kPa      (kPa)
    1497     REAL(WP) ::  d_tmrt       !< delta-tmrt               (°C)
     1506    REAL(WP) ::  d_tmrt       !< delta-tmrt               (degree_C)
    14981507    REAL(WP) ::  va           !< wind speed at 10 m above ground level    (m/s)
    1499     REAL(WP) ::  offset       !< utci deviation by ta cond. exceeded      (°C)
     1508    REAL(WP) ::  offset       !< utci deviation by ta cond. exceeded      (degree_C)
    15001509    REAL(WP) ::  part_ta      !< Air temperature related part of the regression
    15011510    REAL(WP) ::  ta2          !< 2 times ta
     
    18231832! Description:
    18241833! ------------
    1825 !> calculate_perct_static: Estimation of perceived temperature (PT, degC)
     1834!> calculate_perct_static: Estimation of perceived temperature (PT, degree_C)
    18261835!> Value of perct is the Perceived Temperature, degree centigrade
    18271836!------------------------------------------------------------------------------!
     
    18601869    REAL(wp) ::  pmv_s          !< Fangers predicted mean vote for summer clothing
    18611870    REAL(wp) ::  pmva           !< adjusted predicted mean vote
    1862     REAL(wp) ::  ptc            !< perceived temp. for cold conditions (°C)
     1871    REAL(wp) ::  ptc            !< perceived temp. for cold conditions (degree_C)
    18631872    REAL(wp) ::  d_std          !< factor to threshold for sultriness
    18641873    REAL(wp) ::  pmvs           !< pred. mean vote considering sultrieness
    1865     REAL(wp) ::  top            !< Gagge's operative temperatures (°C)
     1874    REAL(wp) ::  top            !< Gagge's operative temperatures (degree_C)
    18661875
    18671876    INTEGER(iwp) :: ncount      !< running index
     
    22442253    REAL(wp) ::  heat_convection  !< energy loss by autocnvection       (W)
    22452254    REAL(wp) ::  activity     !< persons activity  (must stay == actlev, W)
    2246     REAL(wp) ::  t_skin_aver  !< average skin temperature               (°C)
     2255    REAL(wp) ::  t_skin_aver  !< average skin temperature               (degree_C)
    22472256    REAL(wp) ::  bc           !< preliminary result storage
    22482257    REAL(wp) ::  cc           !< preliminary result storage
     
    22502259    REAL(wp) ::  ec           !< preliminary result storage
    22512260    REAL(wp) ::  gc           !< preliminary result storage
    2252     REAL(wp) ::  t_clothing   !< clothing temperature                   (°C)
     2261    REAL(wp) ::  t_clothing   !< clothing temperature                   (degree_C)
    22532262    REAL(wp) ::  hr           !< radiational heat resistence
    22542263    REAL(wp) ::  clo          !< clothing insulation index              (clo)
     
    28922901    REAL(wp), INTENT(in) ::  height     !< Persons height       (m)
    28932902    REAL(wp), INTENT(in) ::  work       !< Current workload     (W)
    2894     REAL(wp), INTENT(in) ::  ta         !< Air Temperature      (°C)
     2903    REAL(wp), INTENT(in) ::  ta         !< Air Temperature      (degree_C)
    28952904    REAL(wp), INTENT(in) ::  vp         !< Vapor pressure       (hPa)
    28962905    REAL(wp), INTENT(in) ::  ws         !< Wind speed in approx. 1.1m (m/s)
    2897     REAL(wp), INTENT(in) ::  tmrt       !< Mean radiant temperature   (°C)
     2906    REAL(wp), INTENT(in) ::  tmrt       !< Mean radiant temperature   (degree_C)
    28982907    REAL(wp), INTENT(in) ::  pair       !< Air pressure         (hPa)
    28992908    REAL(wp), INTENT(in) ::  dt         !< Timestep             (s)
     
    30843093!> SUBROUTINE ipt_cycle
    30853094!> Calculates one timestep for the instationary version of perceived
    3086 !> temperature (iPT, °C) for
     3095!> temperature (iPT, degree_C) for
    30873096!>  - standard measured/predicted meteorological values and TMRT
    30883097!>    as input;
     
    30993108!
    31003109!-- Type of input of the argument list
    3101     REAL(wp), INTENT ( IN )  ::  ta      !< Air temperature             (°C)
     3110    REAL(wp), INTENT ( IN )  ::  ta      !< Air temperature             (degree_C)
    31023111    REAL(wp), INTENT ( IN )  ::  vp      !< Vapor pressure              (hPa)
    3103     REAL(wp), INTENT ( IN )  ::  tmrt    !< Mean radiant temperature    (°C)
     3112    REAL(wp), INTENT ( IN )  ::  tmrt    !< Mean radiant temperature    (degree_C)
    31043113    REAL(wp), INTENT ( IN )  ::  ws      !< Wind speed                  (m/s)
    31053114    REAL(wp), INTENT ( IN )  ::  pair    !< Air pressure                (hPa)
     
    31113120!-- In and output parameters
    31123121    REAL(wp), INTENT (INOUT) ::  storage     !< Heat storage            (W)
    3113     REAL(wp), INTENT (INOUT) ::  t_clothing  !< Clothig temperature     (°C)
     3122    REAL(wp), INTENT (INOUT) ::  t_clothing  !< Clothig temperature     (degree_C)
    31143123!
    31153124!-- Type of output of the argument list
    3116     REAL(wp), INTENT ( OUT ) ::  ipt  !< Instationary perceived temperature (°C)
     3125    REAL(wp), INTENT ( OUT ) ::  ipt  !< Instationary perceived temperature (degree_C)
    31173126!
    31183127!-- Type of internal variables
     
    31913200!
    31923201!--  Input argument types
    3193     REAL(wp), INTENT ( IN )  ::  ta       !< Air temperature          (°C)
    3194     REAL(wp), INTENT ( IN )  ::  tmrt     !< Mean radiant temperature (°C)
     3202    REAL(wp), INTENT ( IN )  ::  ta       !< Air temperature          (degree_C)
     3203    REAL(wp), INTENT ( IN )  ::  tmrt     !< Mean radiant temperature (degree_C)
    31953204    REAL(wp), INTENT ( IN )  ::  pa       !< Vapour pressure          (hPa)
    31963205    REAL(wp), INTENT ( IN )  ::  pair     !< Air pressure             (hPa)
     
    32053214
    32063215    REAL(wp), INTENT (INOUT) ::  s  !< storage var. of energy balance (W/m2)
    3207     REAL(wp), INTENT (INOUT) ::  t_cloth  !< clothing temperature (°C)
     3216    REAL(wp), INTENT (INOUT) ::  t_cloth  !< clothing temperature (degree_C)
    32083217!
    32093218!-- Internal variables
     
    32123221    REAL(wp) ::  f_cl         !< Increase in surface due to clothing    (factor)
    32133222    REAL(wp) ::  heat_convection  !< energy loss by autocnvection       (W)
    3214     REAL(wp) ::  t_skin_aver  !< average skin temperature               (°C)
     3223    REAL(wp) ::  t_skin_aver  !< average skin temperature               (degree_C)
    32153224    REAL(wp) ::  bc           !< preliminary result storage
    32163225    REAL(wp) ::  cc           !< preliminary result storage
     
    32183227    REAL(wp) ::  ec           !< preliminary result storage
    32193228    REAL(wp) ::  gc           !< preliminary result storage
    3220     REAL(wp) ::  t_clothing   !< clothing temperature                   (°C)
     3229    REAL(wp) ::  t_clothing   !< clothing temperature                   (degree_C)
    32213230!     REAL(wp) ::  hr           !< radiational heat resistence
    32223231    REAL(wp) ::  clo          !< clothing insulation index              (clo)
     
    33383347!
    33393348!-- Input arguments:
    3340     REAL(wp), INTENT( IN ) ::  ta    !< Air temperature             (°C)
    3341     REAL(wp), INTENT( IN ) ::  tmrt  !< Mean radiant temperature    (°C)
     3349    REAL(wp), INTENT( IN ) ::  ta    !< Air temperature             (degree_C)
     3350    REAL(wp), INTENT( IN ) ::  tmrt  !< Mean radiant temperature    (degree_C)
    33423351    REAL(wp), INTENT( IN ) ::  v     !< Wind speed                  (m/s)
    33433352    REAL(wp), INTENT( IN ) ::  vpa   !< Vapor pressure              (hPa)
     
    33453354!
    33463355!-- Output arguments:
    3347     REAL(wp), INTENT ( OUT ) ::  pet_ij  !< PET                     (°C)
     3356    REAL(wp), INTENT ( OUT ) ::  pet_ij  !< PET                     (degree_C)
    33483357!
    33493358!-- Internal variables:
     
    33603369    REAL(wp) ::  rtv
    33613370    REAL(wp) ::  vpts       !< Sat. vapor pressure over skin        (hPa)
    3362     REAL(wp) ::  tsk        !< Skin temperature                     (°C)
    3363     REAL(wp) ::  tcl        !< Clothing temperature                 (°C)
     3371    REAL(wp) ::  tsk        !< Skin temperature                     (degree_C)
     3372    REAL(wp) ::  tcl        !< Clothing temperature                 (degree_C)
    33643373    REAL(wp) ::  wetsk      !< Fraction of wet skin                 (factor)
    33653374!
     
    34123421!-- Input arguments:
    34133422    REAL(wp), INTENT( IN )  ::  pair      !< air pressure             (hPa)
    3414     REAL(wp), INTENT( IN )  ::  ta        !< air temperature          (°C)
     3423    REAL(wp), INTENT( IN )  ::  ta        !< air temperature          (degree_C)
    34153424    REAL(wp), INTENT( IN )  ::  vpa       !< vapor pressure           (hPa)
    34163425    REAL(wp), INTENT( IN )  ::  age       !< Persons age              (a)
     
    34743483    REAL(wp), INTENT( IN )  ::  int_heat  !< internal heat production (W)
    34753484    REAL(wp), INTENT( IN )  ::  pair   !< Air pressure             (hPa)
    3476     REAL(wp), INTENT( IN )  ::  ta     !< Air temperature          (°C)
    3477     REAL(wp), INTENT( IN )  ::  tmrt   !< Mean radiant temperature (°C)
     3485    REAL(wp), INTENT( IN )  ::  ta     !< Air temperature          (degree_C)
     3486    REAL(wp), INTENT( IN )  ::  tmrt   !< Mean radiant temperature (degree_C)
    34783487    REAL(wp), INTENT( IN )  ::  v      !< Wind speed               (m/s)
    34793488    REAL(wp), INTENT( IN )  ::  vpa    !< Vapor pressure           (hPa)
     
    34923501    REAL(wp), INTENT( OUT ) ::  rdcl   !< Diffusion resistence of clothing (factor)
    34933502    REAL(wp), INTENT( OUT ) ::  rdsk   !< Diffusion resistence of skin (factor)
    3494     REAL(wp), INTENT( OUT ) ::  tcl    !< Clothing temperature         (°C)
    3495     REAL(wp), INTENT( OUT ) ::  tsk    !< Skin temperature             (°C)
     3503    REAL(wp), INTENT( OUT ) ::  tcl    !< Clothing temperature         (degree_C)
     3504    REAL(wp), INTENT( OUT ) ::  tsk    !< Skin temperature             (degree_C)
    34963505    REAL(wp), INTENT( OUT ) ::  vpts   !< Sat. vapor pressure over skin (hPa)
    34973506    REAL(wp), INTENT( OUT ) ::  wetsk  !< Fraction of wet skin (dimensionless)
     
    35083517!
    35093518!-- Internal variables
    3510     REAL(wp) ::  c(0:10)        !< Core temperature array           (°C)
     3519    REAL(wp) ::  c(0:10)        !< Core temperature array           (degree_C)
    35113520    REAL(wp) ::  cbare          !< Convection through bare skin
    35123521    REAL(wp) ::  cclo           !< Convection through clothing
     
    37533762    REAL(wp), INTENT( IN ) ::  rdsk  !< diffusion resistence of skin (factor)
    37543763    REAL(wp), INTENT( IN ) ::  rtv   !< respiratory volume
    3755     REAL(wp), INTENT( IN ) ::  ta    !< air temperature              (°C)
    3756     REAL(wp), INTENT( IN ) ::  tcl   !< clothing temperature         (°C)
    3757     REAL(wp), INTENT( IN ) ::  tsk   !< skin temperature             (°C)
     3764    REAL(wp), INTENT( IN ) ::  ta    !< air temperature              (degree_C)
     3765    REAL(wp), INTENT( IN ) ::  tcl   !< clothing temperature         (degree_C)
     3766    REAL(wp), INTENT( IN ) ::  tsk   !< skin temperature             (degree_C)
    37583767    REAL(wp), INTENT( IN ) ::  vpts  !< sat. vapor pressure over skin (hPa)
    37593768    REAL(wp), INTENT( IN ) ::  wetsk !< fraction of wet skin (dimensionless)
     
    37613770!-- Output arguments:
    37623771    REAL(wp), INTENT( OUT ) ::  aeff     !< effective surface area       (m²)
    3763     REAL(wp), INTENT( OUT ) ::  pet_ij   !< PET                          (°C)
     3772    REAL(wp), INTENT( OUT ) ::  pet_ij   !< PET                          (degree_C)
    37643773!
    37653774!-- Cconstants:
     
    37823791    REAL ( wp ) ::  rclo              !< Radiational loss of clothing   (W/m²)
    37833792    REAL ( wp ) ::  rsum              !< Radiational loss or gain       (W/m²)
    3784     REAL ( wp ) ::  tex               !< Temperat. of exhaled air       (°C)
     3793    REAL ( wp ) ::  tex               !< Temperat. of exhaled air       (degree_C)
    37853794    REAL ( wp ) ::  vpex              !< Vapor pressure of exhaled air  (hPa)
    37863795    REAL ( wp ) ::  xx                !< Delta PET per iteration        (K)
Note: See TracChangeset for help on using the changeset viewer.