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

    r2350 r2512  
    2626! -----------------
    2727! $Id$
     28! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
     29! no output of ghost layer data
     30!
     31! 2350 2017-08-15 11:48:26Z kanani
    2832! Bugfix and error message for nopointer version.
    2933! Additional "! defined(__nopointer)" as workaround to enable compilation of
     
    24242428        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
    24252429        LOGICAL, INTENT(OUT)           ::  found     !<
    2426         REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
    2427         REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg)     ::  temp_pf    !< temp array for urban surface output procedure
     2430        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
     2431        REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
    24282432       
    24292433        CHARACTER (len=varnamelength)                          :: var, surfid
     
    29002904             
    29012905        END SELECT
    2902        
    2903 !--     fill out array local_pf which is subsequently treated by data_output_3d
    2904         CALL exchange_horiz( temp_pf, nbgp )
    2905 !
    2906 !--  To Do: why reversed loop order
    2907         DO j = nysg,nyng
    2908             DO i = nxlg,nxrg
    2909                 DO k = nzb_do, nzt_do
     2906!
     2907!--     Rearrange dimensions for NetCDF output
     2908        DO  j = nys, nyn
     2909            DO  i = nxl, nxr
     2910                DO  k = nzb_do, nzt_do
    29102911                    local_pf(i,j,k) = temp_pf(k,j,i)
    29112912                ENDDO
Note: See TracChangeset for help on using the changeset viewer.