Changeset 3172


Ignore:
Timestamp:
Jul 26, 2018 12:06:06 PM (6 years ago)
Author:
suehring
Message:

temporal work-around for calculation of effective radiative surface temperature; prevent positive solar radiation during nighttime

File:
1 edited

Legend:

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

    r3170 r3172  
    2828! -----------------
    2929! $Id$
     30! Bugfixes:
     31!  - temporal work-around for calculation of effective radiative surface
     32!    temperature
     33!  - prevent positive solar radiation during nighttime
     34!
     35! 3170 2018-07-25 15:19:37Z suehring
    3036! Bugfix, map signle-column radiation forcing profiles on top of any topography
    3137!
     
    30973103                ENDIF       
    30983104             ENDDO
    3099 
     3105!
     3106!--       Solar radiation is zero during night
     3107          ELSE
     3108             rad_sw_in(k,:,:)  = 0.0_wp
     3109             rad_sw_out(k,:,:) = 0.0_wp
    31003110          ENDIF
    31013111!
     
    35383548                      ENDDO
    35393549                   ENDDO
    3540 
     3550!
     3551!--             Solar radiation is zero during night
     3552                ELSE
     3553                   rad_sw_in(k,j,i)  = 0.0_wp
     3554                   rad_sw_out(k,j,i) = 0.0_wp
    35413555                ENDIF
    35423556
     
    44164430     INTEGER(iwp)                      :: nzubl, nzutl, isurf, isurfsrc, isvf, icsf, ipcgb
    44174431     INTEGER(iwp)                      :: isd                !< solar direction number
     4432     INTEGER(iwp)                      :: pc_box_dimshift    !< transform for best accuracy
     4433     INTEGER(iwp), DIMENSION(0:3)      :: reorder = (/ 1, 0, 3, 2 /)
     4434     
    44184435     REAL(wp), DIMENSION(3,3)          :: mrot               !< grid rotation matrix (zyx)
    44194436     REAL(wp), DIMENSION(3,0:nsurf_type):: vnorm             !< face direction normal vectors (zyx)
     
    44254442     REAL(wp), PARAMETER               :: alpha = 0._wp      !< grid rotation (TODO: add to namelist or remove)
    44264443     REAL(wp)                          :: pc_box_area, pc_abs_frac, pc_abs_eff
    4427      INTEGER(iwp)                      :: pc_box_dimshift    !< transform for best accuracy
    4428      INTEGER(iwp), DIMENSION(0:3)      :: reorder = (/ 1, 0, 3, 2 /)
     4444     REAL(wp)                          ::  count_surfaces    !< number of all surfaces in model domain
     4445     REAL(wp)                          ::  count_surfaces_l  !< number of all surfaces in sub-domain
     4446     REAL(wp)                          ::  pt_surf_urb       !< mean surface temperature of all surfaces in model domain, temporal work-around
     4447     REAL(wp)                          ::  pt_surf_urb_l     !< mean surface temperature of all surfaces in sub-domain, temporal work-around
     4448
    44294449     REAL(wp), DIMENSION(0:nsurf_type) :: facearea
    44304450     REAL(wp)                          :: pabsswl  = 0.0_wp  !< total absorbed SW radiation energy in local processor (W)
     
    44444464     REAL(wp)                          :: area_horl          !< total horizontal area of domain in local processor
    44454465     REAL(wp)                          :: area_hor           !< total horizontal area of domain in all processor
    4446 
    44474466
    44484467
     
    49444963     IF ( area_surf /= 0.0_wp ) &
    49454964          emissivity_urb = emiss_sum_surf / area_surf
     4965!
     4966!--  Temporally comment out calculation of effective radiative temperature.
     4967!--  See below for more explanation.
    49464968!--  (3) temperature
    4947      t_rad_urb = ( (pemitlw - pabslw + emissivity_urb*pinlw) / &
    4948           (emissivity_urb*sigma_sb * area_hor) )**0.25_wp
     4969!      t_rad_urb = ( (pemitlw - pabslw + emissivity_urb*pinlw) / &
     4970!           (emissivity_urb*sigma_sb * area_hor) )**0.25_wp
     4971
     4972!
     4973!--  It has been turned out that the effective radiative temperature is far
     4974!--  too high during nighttime, resulting in unphysical radiative forcing
     4975!--  with wrong signs. For the moment, as a work-around, compute the mean
     4976!--  surface temperature from all surface elements, resulting in more
     4977!--  physically meaningful radiative forcings.           
     4978     pt_surf_urb_l    = 0.0_wp
     4979     count_surfaces_l = 0.0_wp
     4980     DO  m = 1, surf_lsm_h%ns
     4981        k                = surf_lsm_h%k(m)
     4982        pt_surf_urb_l    = pt_surf_urb_l + surf_lsm_h%pt_surface(m)            &
     4983                           * ( hyp(k) / 100000.0_wp )**0.286_wp
     4984        count_surfaces_l = count_surfaces_l + 1.0_wp
     4985     ENDDO
     4986     DO  m = 1, surf_usm_h%ns
     4987        k                = surf_usm_h%k(m)
     4988        pt_surf_urb_l    = pt_surf_urb_l + surf_usm_h%pt_surface(m)            &
     4989                           * ( hyp(k) / 100000.0_wp )**0.286_wp
     4990        count_surfaces_l = count_surfaces_l + 1.0_wp
     4991     ENDDO
     4992     DO  l = 0, 3
     4993        DO  m = 1, surf_lsm_v(l)%ns
     4994           k                = surf_lsm_v(l)%k(m)
     4995           pt_surf_urb_l    = pt_surf_urb_l + surf_lsm_v(l)%pt_surface(m)      &
     4996                           * ( hyp(k) / 100000.0_wp )**0.286_wp
     4997           count_surfaces_l = count_surfaces_l + 1.0_wp
     4998        ENDDO
     4999        DO  m = 1, surf_usm_v(l)%ns
     5000           k                = surf_usm_v(l)%k(m)
     5001           pt_surf_urb_l    = pt_surf_urb_l + surf_usm_v(l)%pt_surface(m)      &
     5002                           * ( hyp(k) / 100000.0_wp )**0.286_wp
     5003           count_surfaces_l = count_surfaces_l + 1.0_wp
     5004        ENDDO
     5005     ENDDO
     5006     
     5007     pt_surf_urb    = 0.0_wp
     5008     count_surfaces = 0.0_wp
     5009     
     5010#if defined( __parallel )
     5011     CALL MPI_ALLREDUCE( count_surfaces_l, count_surfaces, 1, MPI_REAL,        &
     5012                         MPI_SUM, comm2d, ierr)
     5013     CALL MPI_ALLREDUCE( pt_surf_urb_l,  pt_surf_urb,      1, MPI_REAL,        &
     5014                         MPI_SUM, comm2d, ierr)
     5015#else
     5016     count_surfaces_l = count_surfaces
     5017     pt_surf_urb_l    = pt_surf_urb
     5018#endif     
     5019
     5020     t_rad_urb = pt_surf_urb / count_surfaces
    49495021     
    49505022    CONTAINS
Note: See TracChangeset for help on using the changeset viewer.