Ignore:
Timestamp:
Apr 10, 2020 9:49:43 AM (5 years ago)
Author:
pavelkrc
Message:

Merge brach resler

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/radiation_model_mod.f90

    r4481 r4493  
    2828! -----------------
    2929! $Id$
     30! Avoid unstable direct normal radiation near horizon
     31!
     32! 4481 2020-03-31 18:55:54Z maronga
    3033! use statement for exchange horiz added
    3134!
     
    454457                sky_trans,                       & !< sky transmissivity
    455458                time_radiation = 0.0_wp,         & !< time since last call of radiation code
    456                 trace_fluxes_above = -1.0_wp       !< NAMELIST option for debug tracing of large radiative fluxes (W/m2;W/m3)
     459                trace_fluxes_above = -1.0_wp,    & !< NAMELIST option for debug tracing of large radiative fluxes (W/m2;W/m3)
     460                min_stable_coszen = 0.0262_wp      !< 1.5 deg above horizon, eliminates most of circumsolar
    457461
    458462    INTEGER(iwp) ::  day_of_year   !< day of the current year
     
    58065810     REAL(wp)                          ::  area_surf          !< total area of surfaces in all processor
    58075811     REAL(wp)                          ::  area_hor           !< total horizontal area of domain in all processor
     5812     REAL(wp)                          ::  sun_direct_factor  !< factor for direct normal radiation from direct horizontal
    58085813#if defined( __parallel )
    58095814     REAL(wp), DIMENSION(1:7)          ::  combine_allreduce   !< dummy array used to combine several MPI_ALLREDUCE calls
     
    60196024        mrtinlw(imrt) = mrtsky(imrt) * rad_lw_in_diff(j,i)
    60206025     ENDDO
    6021 
    6022      !-- direct radiation
     6026!
     6027!--  Direct radiation
    60236028     IF ( cos_zenith > 0 )  THEN
    6024         !--Identify solar direction vector (discretized number) 1)
    6025         !--
     6029!
     6030!--     To avoid numerical instability near horizon depending on what direct
     6031!--     radiation is used (slightly different zenith angle, considering
     6032!--     circumsolar etc.), we use a minimum value for cos_zenith
     6033        sun_direct_factor = 1._wp / MAX(min_stable_coszen, cos_zenith)
     6034!
     6035!--     Identify solar direction vector (discretized number) (1)
    60266036        j = FLOOR(ACOS(cos_zenith) / pi * raytrace_discrete_elevs)
    60276037        i = MODULO(NINT(ATAN2(sun_dir_lon, sun_dir_lat)               &
     
    60346044           i = surfl(ix, isurf)
    60356045           surfinswdir(isurf) = rad_sw_in_dir(j,i) *                        &
    6036                 costheta(surfl(id, isurf)) * dsitrans(isurf, isd) / cos_zenith
     6046                costheta(surfl(id, isurf)) * dsitrans(isurf, isd) * sun_direct_factor
    60376047        ENDDO
    60386048!
     
    60426052           i = mrtbl(ix, imrt)
    60436053           mrtinsw(imrt) = mrtinsw(imrt) + mrtdsit(imrt, isd) * rad_sw_in_dir(j,i) &
    6044                                      / cos_zenith / 4.0_wp ! normal to sphere
     6054                                     * sun_direct_factor / 4.0_wp ! normal to sphere
    60456055        ENDDO
    60466056     ENDIF
     
    60856095                   pc_abs_frac = 1.0_wp - exp(pc_abs_eff * lad_s(k,j,i))
    60866096!
    6087 !--                isd has already been established, see 1)
     6097!--                isd has already been established, see (1)
    60886098                   pcbinswdir(ipcgb) = rad_sw_in_dir(j, i) * pc_box_area &
    60896099                                       * pc_abs_frac * dsitransc(ipcgb, isd)
     
    78677877
    78687878!--
    7869 !--     Raytrace to canopy boxes to fill dsitransc TODO optimize
     7879!--     Raytrace to canopy boxes to fill dsitransc
     7880!--     TODO: consider replacing by DSI rays toward surfaces
    78707881        dsitransc(:,:) = 0._wp
    78717882        az0 = 0._wp
Note: See TracChangeset for help on using the changeset viewer.