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_3d.f90

    r2101 r2512  
    2525! -----------------
    2626! $Id$
     27! ghost layer points removed from output array local_pf
     28!
     29! 2101 2017-01-05 16:42:31Z suehring
    2730!
    2831! 2000 2016-08-20 18:09:15Z knoop
     
    7881    LOGICAL      ::  found !<
    7982
    80    REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) ::  local_pf !<
     83   REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    8184
    8285
     
    9295!       CASE ( 'u2' )
    9396!          IF ( av == 0 )  THEN
    94 !             DO  i = nxlg, nxrg
    95 !                DO  j = nysg, nyng
     97!             DO  i = nxl, nxr
     98!                DO  j = nys, nyn
    9699!                   DO  k = nzb_do, nzt_do
    97100!                      local_pf(i,j,k) = u2(k,j,i)
     
    100103!             ENDDO
    101104!          ELSE
    102 !             DO  i = nxlg, nxrg
    103 !                DO  j = nysg, nyng
     105!             DO  i = nxl, nxr
     106!                DO  j = nys, nyn
    104107!                   DO  k = nzb_do, nzt_do
    105108!                      local_pf(i,j,k) = u2_av(k,j,i)
Note: See TracChangeset for help on using the changeset viewer.