Ignore:
Timestamp:
Apr 27, 2018 12:33:25 PM (6 years ago)
Author:
Giersch
Message:

precipitation_rate removed, further allocation checks for data output of averaged quantities implemented, double CALL of flow_statistics at the beginning of time_integration removed, further minor bugfixes, comments added

File:
1 edited

Legend:

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

    r2932 r3004  
    2525! -----------------
    2626! $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
    2731! renamed uvexposure_par to biometeorology_parameters
    2832!
     
    331335    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    332336
     337    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     338
    333339    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
    334340
     
    353359
    354360       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
    355365          IF ( av == 1 )  THEN
    356366             DO  i = nxl, nxr
     
    502512
    503513          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
    507519                ENDDO
    508              ENDDO
     520             ENDIF
    509521
    510522
Note: See TracChangeset for help on using the changeset viewer.