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/user_data_output_3d.f90

    r2718 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! 2718 2018-01-02 08:49:38Z maronga
    2731! Corrected "Former revisions" section
    2832!
     
    8791    LOGICAL      ::  found !<
    8892
    89    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     93    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     94
     95    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    9096
    9197
     
    109115!             ENDDO
    110116!          ELSE
     117!             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     118!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     119!                u2_av = REAL( fill_value, KIND = wp )
     120!             ENDIF
    111121!             DO  i = nxl, nxr
    112122!                DO  j = nys, nyn
Note: See TracChangeset for help on using the changeset viewer.