Changeset 4493 for palm/trunk/SOURCE/radiation_model_mod.f90
- Timestamp:
- Apr 10, 2020 9:49:43 AM (5 years ago)
- Location:
- palm/trunk
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk
- Property svn:mergeinfo changed
/palm/branches/resler merged: 4491-4492
- Property svn:mergeinfo changed
-
palm/trunk/SOURCE
- Property svn:mergeinfo changed
/palm/branches/resler/SOURCE merged: 4491-4492
- Property svn:mergeinfo changed
-
palm/trunk/SOURCE/radiation_model_mod.f90
- Property svn:mergeinfo changed
/palm/branches/resler/SOURCE/radiation_model_mod.f90 merged: 4491-4492
r4481 r4493 28 28 ! ----------------- 29 29 ! $Id$ 30 ! Avoid unstable direct normal radiation near horizon 31 ! 32 ! 4481 2020-03-31 18:55:54Z maronga 30 33 ! use statement for exchange horiz added 31 34 ! … … 454 457 sky_trans, & !< sky transmissivity 455 458 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 457 461 458 462 INTEGER(iwp) :: day_of_year !< day of the current year … … 5806 5810 REAL(wp) :: area_surf !< total area of surfaces in all processor 5807 5811 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 5808 5813 #if defined( __parallel ) 5809 5814 REAL(wp), DIMENSION(1:7) :: combine_allreduce !< dummy array used to combine several MPI_ALLREDUCE calls … … 6019 6024 mrtinlw(imrt) = mrtsky(imrt) * rad_lw_in_diff(j,i) 6020 6025 ENDDO 6021 6022 !-- direct radiation6026 ! 6027 !-- Direct radiation 6023 6028 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) 6026 6036 j = FLOOR(ACOS(cos_zenith) / pi * raytrace_discrete_elevs) 6027 6037 i = MODULO(NINT(ATAN2(sun_dir_lon, sun_dir_lat) & … … 6034 6044 i = surfl(ix, isurf) 6035 6045 surfinswdir(isurf) = rad_sw_in_dir(j,i) * & 6036 costheta(surfl(id, isurf)) * dsitrans(isurf, isd) / cos_zenith6046 costheta(surfl(id, isurf)) * dsitrans(isurf, isd) * sun_direct_factor 6037 6047 ENDDO 6038 6048 ! … … 6042 6052 i = mrtbl(ix, imrt) 6043 6053 mrtinsw(imrt) = mrtinsw(imrt) + mrtdsit(imrt, isd) * rad_sw_in_dir(j,i) & 6044 / cos_zenith/ 4.0_wp ! normal to sphere6054 * sun_direct_factor / 4.0_wp ! normal to sphere 6045 6055 ENDDO 6046 6056 ENDIF … … 6085 6095 pc_abs_frac = 1.0_wp - exp(pc_abs_eff * lad_s(k,j,i)) 6086 6096 ! 6087 !-- isd has already been established, see 1)6097 !-- isd has already been established, see (1) 6088 6098 pcbinswdir(ipcgb) = rad_sw_in_dir(j, i) * pc_box_area & 6089 6099 * pc_abs_frac * dsitransc(ipcgb, isd) … … 7867 7877 7868 7878 !-- 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 7870 7881 dsitransc(:,:) = 0._wp 7871 7882 az0 = 0._wp - Property svn:mergeinfo changed
Note: See TracChangeset
for help on using the changeset viewer.