Changeset 3004 for palm/trunk/SOURCE/uv_exposure_model_mod.f90
- Timestamp:
- Apr 27, 2018 12:33:25 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/uv_exposure_model_mod.f90
r2932 r3004 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Further allocation checks implemented (averaged data will be assigned to fill 28 ! values if no allocation happened so far) 29 ! 30 ! 2932 2018-03-26 09:39:22Z maronga 27 31 ! renamed uvexposure_par to biometeorology_parameters 28 32 ! … … 331 335 LOGICAL :: two_d !< flag parameter that indicates 2D variables (horizontal cross sections) 332 336 337 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 338 333 339 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) :: local_pf !< 334 340 … … 353 359 354 360 CASE ( 'uvem_vitd3dose*_xy' ) ! 2d-array 361 IF ( .NOT. ALLOCATED( vitd3_exposure_av ) ) THEN 362 ALLOCATE( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) ) 363 vitd3_exposure_av = REAL( fill_value, KIND = wp ) 364 ENDIF 355 365 IF ( av == 1 ) THEN 356 366 DO i = nxl, nxr … … 502 512 503 513 CASE ( 'uvem_vitd3dose*' ) 504 DO i = nxlg, nxrg 505 DO j = nysg, nyng 506 vitd3_exposure_av(j,i) = vitd3_exposure_av(j,i) + vitd3_exposure(j,i) 514 IF ( ALLOCATED( vitd3_exposure_av ) ) THEN 515 DO i = nxlg, nxrg 516 DO j = nysg, nyng 517 vitd3_exposure_av(j,i) = vitd3_exposure_av(j,i) + vitd3_exposure(j,i) 518 ENDDO 507 519 ENDDO 508 END DO520 ENDIF 509 521 510 522
Note: See TracChangeset
for help on using the changeset viewer.