Changeset 4126 for palm


Ignore:
Timestamp:
Jul 30, 2019 11:09:11 AM (5 years ago)
Author:
gronemeier
Message:

renaming in biometeorology_mod, adding of example cases for biometeorolgy

Location:
palm/trunk
Files:
9 added
2 edited

Legend:

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

    r3885 r4126  
    2727! -----------------
    2828! $Id$
     29! renamed vitd3_exposure_av into vitd3_dose,
     30! renamed uvem_calc_exposure into bio_calculate_uv_exposure
     31!
     32! 3885 2019-04-11 11:29:34Z kanani
    2933! Changes related to global restructuring of location messages and introduction
    3034! of additional debug messages
     
    274278    REAL(wp), DIMENSION(0:71,0:9) ::  radiance_array_temp          = 0.0_wp  !< temporary radiance data
    275279
    276     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_exposure     !< result variable for instantaneous vitamin-D weighted exposures
    277     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_exposure_av  !< result variable for summation of vitamin-D weighted exposures
     280    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_exposure  !< result variable for instantaneous vitamin-D weighted exposures
     281    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_dose      !< result variable for summation of vitamin-D weighted exposures
    278282
    279283    REAL(wp), DIMENSION(0:35,0:9,0:90) ::  radiance_lookup_table   = 0.0_wp  !< radiance lookup table
     
    290294!
    291295!-- UVEM PUBLIC variables and methods
    292     PUBLIC uvem_calc_exposure, uv_exposure
     296    PUBLIC bio_calculate_uv_exposure, uv_exposure
    293297
    294298!
     
    386390!
    387391!-- Calculate UV exposure grid
    388     INTERFACE uvem_calc_exposure
    389        MODULE PROCEDURE uvem_calc_exposure
    390     END INTERFACE uvem_calc_exposure
     392    INTERFACE bio_calculate_uv_exposure
     393       MODULE PROCEDURE bio_calculate_uv_exposure
     394    END INTERFACE bio_calculate_uv_exposure
    391395
    392396 CONTAINS
     
    462466
    463467          CASE ( 'uvem_vitd3dose*' )
    464              IF ( .NOT. ALLOCATED( vitd3_exposure_av ) )  THEN
    465                 ALLOCATE( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) )
     468             IF ( .NOT. ALLOCATED( vitd3_dose ) )  THEN
     469                ALLOCATE( vitd3_dose(nysg:nyng,nxlg:nxrg) )
    466470             ENDIF
    467              vitd3_exposure_av = 0.0_wp
     471             vitd3_dose = 0.0_wp
    468472
    469473          CASE DEFAULT
     
    607611!--       This is a cumulated dose. No mode == 'average' for this quantity.
    608612          CASE ( 'uvem_vitd3dose*' )
    609              IF ( ALLOCATED( vitd3_exposure_av ) )  THEN
     613             IF ( ALLOCATED( vitd3_dose ) )  THEN
    610614                DO  i = nxlg, nxrg
    611615                   DO  j = nysg, nyng
    612                       vitd3_exposure_av(j,i) = vitd3_exposure_av(j,i) + vitd3_exposure(j,i)
     616                      vitd3_dose(j,i) = vitd3_dose(j,i) + vitd3_exposure(j,i)
    613617                   ENDDO
    614618                ENDDO
     
    805809
    806810       CASE ( 'uvem_vitd3*' )
    807           IF (  .NOT.  uv_exposure )  THEN
    808              message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    809                       'res a namelist &uvexposure_par'
    810              CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
    811           ENDIF
     811!           IF (  .NOT.  uv_exposure )  THEN
     812!              message_string = 'output of "' // TRIM( var ) // '" requi' //     &
     813!                       'res a namelist &uvexposure_par'
     814!              CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
     815!           ENDIF
    812816          IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    813817             message_string = 'illegal value for data_output: "' //            &
     
    823827
    824828       CASE ( 'uvem_vitd3dose*' )
    825           IF (  .NOT.  uv_exposure )  THEN
    826              message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    827                       'res  a namelist &uvexposure_par'
    828              CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
    829           ENDIF
     829!           IF (  .NOT.  uv_exposure )  THEN
     830!              message_string = 'output of "' // TRIM( var ) // '" requi' //     &
     831!                       'res  a namelist &uvexposure_par'
     832!              CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
     833!           ENDIF
    830834          IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    831835             message_string = 'illegal value for data_output: "' //            &
     
    835839          ENDIF
    836840          unit = 'IU/av-h'
    837           IF ( .NOT. ALLOCATED( vitd3_exposure_av ) )  THEN
    838              ALLOCATE( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) )
     841          IF ( .NOT. ALLOCATED( vitd3_dose ) )  THEN
     842             ALLOCATE( vitd3_dose(nysg:nyng,nxlg:nxrg) )
    839843          ENDIF
    840           vitd3_exposure_av = 0.0_wp
     844          vitd3_dose = 0.0_wp
    841845
    842846       CASE DEFAULT
     
    10301034             DO  i = nxl, nxr
    10311035                DO  j = nys, nyn
    1032                    local_pf(i,j,nzb+1) = vitd3_exposure_av(j,i)
     1036                   local_pf(i,j,nzb+1) = vitd3_dose(j,i)
    10331037                ENDDO
    10341038             ENDDO
     
    12501254        ONLY: message_string
    12511255
    1252     IF ( .NOT. radiation_interactions )  THEN
     1256    IF ( (.NOT. radiation_interactions) .AND. ( thermal_comfort ) )  THEN
    12531257       message_string = 'The mrt calculation requires ' //                     &
    12541258                        'enabled radiation_interactions but it ' //            &
     
    42904294!> Module-specific routine for new module
    42914295!---------------------------------------------------------------------------------------------------------------------!
    4292  SUBROUTINE uvem_calc_exposure
     4296 SUBROUTINE bio_calculate_uv_exposure
    42934297
    42944298    USE indices,                                                                                                      &
     
    44394443    ENDIF
    44404444
    4441  END SUBROUTINE uvem_calc_exposure
     4445 END SUBROUTINE bio_calculate_uv_exposure
    44424446
    44434447 END MODULE biometeorology_mod
  • palm/trunk/SOURCE/time_integration.f90

    r4111 r4126  
    2525! -----------------
    2626! $Id$
     27! renamed routine to calculate uv exposure
     28!
     29! 4111 2019-07-22 18:16:57Z suehring
    2730! advc_flags_1 / advc_flags_2 renamed to advc_flags_m / advc_flags_s
    2831!
     
    545548
    546549    USE biometeorology_mod,                                                                        &
    547         ONLY:  bio_calculate_thermal_index_maps, thermal_comfort, uvem_calc_exposure, uv_exposure
     550        ONLY:  bio_calculate_thermal_index_maps, thermal_comfort, bio_calculate_uv_exposure,       &
     551               uv_exposure
    548552
    549553    USE bulk_cloud_model_mod,                                                                      &
     
    17041708!--       If required, do UV exposure calculations
    17051709          IF ( uv_exposure )  THEN
    1706              CALL uvem_calc_exposure
     1710             CALL bio_calculate_uv_exposure
    17071711          ENDIF
    17081712       ENDIF
Note: See TracChangeset for help on using the changeset viewer.