Ignore:
Timestamp:
Oct 4, 2017 8:26:59 AM (7 years ago)
Author:
raasch
Message:

upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny; no output if redundant ghost layer data to NetCDF files

File:
1 edited

Legend:

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

    r2233 r2512  
    2525! -----------------
    2626! $Id$
     27! ghost layer points removed from output array local_pf
     28!
     29! 2233 2017-05-30 18:08:54Z suehring
    2730!
    2831! 2232 2017-05-30 17:47:52Z suehring
     
    8588    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    8689
    87     REAL(wp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nzt+1) ::  local_pf !<
     90    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
    8891
    8992
     
    99102!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
    100103!          IF ( av == 0 )  THEN
    101 !             DO  i = nxlg, nxrg
    102 !                DO  j = nysg, nyng
     104!             DO  i = nxl, nxr
     105!                DO  j = nys, nyn
    103106!                   DO  k = nzb_do, nzt_do
    104107!                      local_pf(i,j,k) = u2(k,j,i)
     
    107110!             ENDDO
    108111!          ELSE
    109 !             DO  i = nxlg, nxrg
    110 !                DO  j = nysg, nyng
     112!             DO  i = nxl, nxr
     113!                DO  j = nys, nyn
    111114!                   DO  k = nzb_do, nzt_do
    112115!                      local_pf(i,j,k) = u2_av(k,j,i)
     
    118121!          grid = 'zu'
    119122!
    120 !--    In case two-dimensional surface variables are outputted, the user
     123!--    In case two-dimensional surface variables are output, the user
    121124!--    has to access related surface-type. Uncomment and extend following lines
    122125!--    appropriately (example output of vertical surface momentum flux of u-
     
    160163
    161164 END SUBROUTINE user_data_output_2d
    162 
Note: See TracChangeset for help on using the changeset viewer.