Changeset 3824 for palm/trunk/SOURCE/chem_photolysis_mod.f90
- Timestamp:
- Mar 27, 2019 3:56:16 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chem_photolysis_mod.f90
r3614 r3824 234 234 235 235 USE radiation_model_mod, & 236 ONLY: calc_zenith, zenith236 ONLY: calc_zenith, cos_zenith 237 237 238 238 IMPLICIT NONE … … 247 247 CALL calc_zenith 248 248 249 IF ( zenith(0)> 0.0_wp ) THEN250 coszi = 1. / zenith(0)249 IF ( cos_zenith > 0.0_wp ) THEN 250 coszi = 1. / cos_zenith 251 251 252 252 DO iphot = 1,nphot … … 254 254 IF ( TRIM( names_s(iav) ) == TRIM( phot_names(iphot) ) ) then 255 255 phot_frequen(iphot)%freq(nzb+1:nzt,:,:) = & 256 par_l(iav) * zenith(0)**par_m(iav) * EXP( -par_n(iav) * coszi )256 par_l(iav) * cos_zenith**par_m(iav) * EXP( -par_n(iav) * coszi ) 257 257 ENDIF 258 258 ENDDO
Note: See TracChangeset
for help on using the changeset viewer.