Changeset 2512


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

Location:
palm/trunk
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SCRIPTS/palmrun

    r2507 r2512  
    662662
    663663
    664              # CHECK, IF DIRECTORY IS UNDER SVN CONTROL
    665           if [[ ! -d .svn ]]
     664             # CHECK, IF TRUNK-DIRECTORY IS UNDER SVN CONTROL
     665          if [[ ! -d ../.svn ]]
    666666          then
    667667             printf "\n\n  +++ source directory"
    668668             printf "\n         \"$source_path\" "
    669669             printf "\n         is not under control of \"subversion\"."
    670              printf "\n         Please do not use palmmrun-option \"-s LM\"\n"
     670             printf "\n         Please do not use palmrun-option \"-s LM\"\n"
    671671          fi
    672672
  • palm/trunk/SOURCE/check_open.f90

    r2300 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29! iso2d-related parts removed
     30!
     31! 2300 2017-06-29 13:31:14Z raasch
    2732! -host
    2833!
     
    178183    CHARACTER (LEN=2)   ::  mask_char               !<
    179184    CHARACTER (LEN=2)   ::  suffix                  !<
    180     CHARACTER (LEN=20)  ::  xtext = 'time in s'     !<
    181185    CHARACTER (LEN=30)  ::  filename                !<
    182186    CHARACTER (LEN=80)  ::  rtext                   !<
    183     CHARACTER (LEN=100) ::  batch_scp               !<
    184187    CHARACTER (LEN=100) ::  line                    !<
    185     CHARACTER (LEN=400) ::  command                 !<
    186188
    187189    INTEGER(iwp) ::  av          !<
    188     INTEGER(iwp) ::  numline = 1 !<
    189     INTEGER(iwp) ::  cranz       !<
    190190    INTEGER(iwp) ::  file_id     !<
    191191    INTEGER(iwp) ::  i           !<
    192     INTEGER(iwp) ::  iaddres     !<
    193192    INTEGER(iwp) ::  ioerr       !< IOSTAT flag for IO-commands ( 0 = no error )
    194     INTEGER(iwp) ::  iusern      !<
    195193    INTEGER(iwp) ::  j           !<
    196194    INTEGER(iwp) ::  k           !<
    197     INTEGER(iwp) ::  legpos = 1  !<
    198     INTEGER(iwp) ::  timodex = 1 !<
    199195   
    200     INTEGER(iwp), DIMENSION(10) ::  klist !<
    201 
    202     LOGICAL ::  datleg = .TRUE.               !<
    203     LOGICAL ::  get_filenames                 !<
    204     LOGICAL ::  grid = .TRUE.                 !<
    205     LOGICAL ::  netcdf_extend                 !<
    206     LOGICAL ::  rand = .TRUE.                 !<
    207     LOGICAL ::  swap = .TRUE.                 !<
    208     LOGICAL ::  twoxa = .TRUE.                !<
    209     LOGICAL ::  twoya = .TRUE.                !<
    210 
    211     REAL(wp) ::  ansx = -999.999_wp !<
    212     REAL(wp) ::  ansy = -999.999_wp !<
    213     REAL(wp) ::  gwid = 0.1_wp      !<
    214     REAL(wp) ::  rlegfak = 1.5_wp   !<
    215     REAL(wp) ::  sizex = 250.0_wp   !<
    216     REAL(wp) ::  sizey = 40.0_wp    !<
    217     REAL(wp) ::  texfac = 1.5_wp    !<
    218 
    219     REAL(wp), DIMENSION(:), ALLOCATABLE      ::  eta !<
    220     REAL(wp), DIMENSION(:), ALLOCATABLE      ::  ho  !<
    221     REAL(wp), DIMENSION(:), ALLOCATABLE      ::  hu  !<
    222  
    223 
    224 
    225     NAMELIST /RAHMEN/  numline, cranz, datleg, rtext, swap
    226     NAMELIST /CROSS/   ansx, ansy, grid, gwid, klist, legpos,                  &
    227                        rand, rlegfak, sizex, sizey, texfac,                    &
    228                        timodex, twoxa, twoya, xtext
    229                        
     196    LOGICAL ::  netcdf_extend    !<
    230197
    231198!
     
    422389          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
    423390!
    424 !--          Output for combine_plot_fields
     391!--          Write index bounds of total domain for combine_plot_fields
    425392             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
    426                 WRITE (21)  -nbgp, nx+nbgp, -nbgp, ny+nbgp    ! total array size
    427                 WRITE (21)   0, nx+1,  0, ny+1    ! output part
    428              ENDIF
    429 !
    430 !--          Determine and write ISO2D coordiante header
    431              ALLOCATE( eta(0:ny+1), ho(0:nx+1), hu(0:nx+1) )
    432              hu = 0.0_wp
    433              ho = (ny+1) * dy
    434              DO  i = 1, ny
    435                 eta(i) = REAL( i ) / ( ny + 1.0_wp )
    436              ENDDO
    437              eta(0)    = 0.0_wp
    438              eta(ny+1) = 1.0_wp
    439 
    440              WRITE (21)  dx,eta,hu,ho
    441              DEALLOCATE( eta, ho, hu )
     393                WRITE (21)   0, nx,  0, ny
     394             ENDIF
    442395
    443396          ENDIF
     
    455408          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
    456409!
    457 !--          Output for combine_plot_fields
     410!--          Write index bounds of total domain for combine_plot_fields
    458411             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
    459                 WRITE (22)  -nbgp, nx+nbgp, 0, nz+1    ! total array size
    460                 WRITE (22)   0, nx+1, 0, nz+1    ! output part
    461              ENDIF
    462 !
    463 !--          Determine and write ISO2D coordinate header
    464              ALLOCATE( eta(0:nz+1), ho(0:nx+1), hu(0:nx+1) )
    465              hu = 0.0_wp
    466              ho = zu(nz+1)
    467              DO  i = 1, nz
    468                 eta(i) = REAL( zu(i) ) / zu(nz+1)
    469              ENDDO
    470              eta(0)    = 0.0_wp
    471              eta(nz+1) = 1.0_wp
    472 
    473              WRITE (22)  dx,eta,hu,ho
    474              DEALLOCATE( eta, ho, hu )
     412                WRITE (22)   0, nx, 0, nz+1    ! output part
     413             ENDIF
    475414
    476415          ENDIF
     
    488427          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
    489428!
    490 !--          Output for combine_plot_fields
     429!--          Write index bounds of total domain for combine_plot_fields
    491430             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
    492                 WRITE (23)  -nbgp, ny+nbgp, 0, nz+1    ! total array size
    493                 WRITE (23)   0, ny+1, 0, nz+1    ! output part
    494              ENDIF
    495 !
    496 !--          Determine and write ISO2D coordiante header
    497              ALLOCATE( eta(0:nz+1), ho(0:ny+1), hu(0:ny+1) )
    498              hu = 0.0_wp
    499              ho = zu(nz+1)
    500              DO  i = 1, nz
    501                 eta(i) = REAL( zu(i) ) / zu(nz+1)
    502              ENDDO
    503              eta(0)    = 0.0_wp
    504              eta(nz+1) = 1.0_wp
    505 
    506              WRITE (23)  dx,eta,hu,ho
    507              DEALLOCATE( eta, ho, hu )
     431                WRITE (23)   0, ny, 0, nz+1    ! output part
     432             ENDIF
    508433
    509434          ENDIF
     
    514439                     FORM='UNFORMATTED' )
    515440!
    516 !--       Write coordinate file for AVS
     441!--       Specifications for combine_plot_fields
    517442          IF ( myid == 0 )  THEN
    518443#if defined( __parallel )
    519 !
    520 !--          Specifications for combine_plot_fields
    521              WRITE ( 30 )  -nbgp,nx+nbgp,-nbgp,ny+nbgp
    522              WRITE ( 30 )  0,nx+1,0,ny+1,0,nz_do3d
     444             WRITE ( 30 )  0, nx, 0, ny, 0, nz_do3d
    523445#endif
    524446          ENDIF
  • palm/trunk/SOURCE/data_output_2d.f90

    r2292 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of cross section output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29!
     30! 2292 2017-06-20 09:51:42Z schwenkel
    2731! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
    2832! includes two more prognostic equations for cloud drop concentration (nc) 
     
    165169! Description:
    166170! ------------
    167 !> Data output of horizontal cross-sections in netCDF format or binary format
    168 !> compatible to old graphic software iso2d.
     171!> Data output of cross-sections in netCDF format or binary format
     172!> to be later converted to NetCDF by helper routine combine_plot_fields.
    169173!> Attention: The position of the sectional planes is still not always computed
    170174!> ---------  correctly. (zu is used always)!
     
    201205       
    202206    USE indices,                                                               &
    203         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg,       &
    204                nz, nzb, nzt
     207        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nz, nzb, nzt
    205208               
    206209    USE kinds
     
    271274    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d            !<
    272275    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d_l          !<
    273     REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  tmp_2d              !< temporary field used to exchange surface-related quantities
    274276
    275277    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf            !<
     
    303305       CASE ( 'xy' )
    304306          s_ind = 1
    305           ALLOCATE( level_z(nzb:nzt+1), local_2d(nxlg:nxrg,nysg:nyng) )
     307          ALLOCATE( level_z(nzb:nzt+1), local_2d(nxl:nxr,nys:nyn) )
    306308
    307309          IF ( netcdf_data_format > 4 )  THEN
     
    311313             ENDDO
    312314             ns = ns - 1
    313              ALLOCATE( local_2d_sections(nxlg:nxrg,nysg:nyng,1:ns) )
     315             ALLOCATE( local_2d_sections(nxl:nxr,nys:nyn,1:ns) )
    314316             local_2d_sections = 0.0_wp
    315317          ENDIF
     
    325327             IF ( myid == 0 )  THEN
    326328#if defined( __parallel )
    327                 ALLOCATE( total_2d(-nbgp:nx+nbgp,-nbgp:ny+nbgp) )
     329                ALLOCATE( total_2d(0:nx,0:ny) )
    328330#endif
    329331             ENDIF
     
    332334       CASE ( 'xz' )
    333335          s_ind = 2
    334           ALLOCATE( local_2d(nxlg:nxrg,nzb:nzt+1) )
     336          ALLOCATE( local_2d(nxl:nxr,nzb:nzt+1) )
    335337
    336338          IF ( netcdf_data_format > 4 )  THEN
     
    340342             ENDDO
    341343             ns = ns - 1
    342              ALLOCATE( local_2d_sections(nxlg:nxrg,1:ns,nzb:nzt+1) )
    343              ALLOCATE( local_2d_sections_l(nxlg:nxrg,1:ns,nzb:nzt+1) )
     344             ALLOCATE( local_2d_sections(nxl:nxr,1:ns,nzb:nzt+1) )
     345             ALLOCATE( local_2d_sections_l(nxl:nxr,1:ns,nzb:nzt+1) )
    344346             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
    345347          ENDIF
     
    356358             IF ( myid == 0 )  THEN
    357359#if defined( __parallel )
    358                 ALLOCATE( total_2d(-nbgp:nx+nbgp,nzb:nzt+1) )
     360                ALLOCATE( total_2d(0:nx,nzb:nzt+1) )
    359361#endif
    360362             ENDIF
     
    363365       CASE ( 'yz' )
    364366          s_ind = 3
    365           ALLOCATE( local_2d(nysg:nyng,nzb:nzt+1) )
     367          ALLOCATE( local_2d(nys:nyn,nzb:nzt+1) )
    366368
    367369          IF ( netcdf_data_format > 4 )  THEN
     
    371373             ENDDO
    372374             ns = ns - 1
    373              ALLOCATE( local_2d_sections(1:ns,nysg:nyng,nzb:nzt+1) )
    374              ALLOCATE( local_2d_sections_l(1:ns,nysg:nyng,nzb:nzt+1) )
     375             ALLOCATE( local_2d_sections(1:ns,nys:nyn,nzb:nzt+1) )
     376             ALLOCATE( local_2d_sections_l(1:ns,nys:nyn,nzb:nzt+1) )
    375377             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
    376378          ENDIF
     
    387389             IF ( myid == 0 )  THEN
    388390#if defined( __parallel )
    389                 ALLOCATE( total_2d(-nbgp:ny+nbgp,nzb:nzt+1) )
     391                ALLOCATE( total_2d(0:ny,nzb:nzt+1) )
    390392#endif
    391393             ENDIF
     
    434436!
    435437!-- Allocate a temporary array for resorting (kji -> ijk).
    436     ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb:nzt+1) )
     438    ALLOCATE( local_pf(nxl:nxr,nys:nyn,nzb:nzt+1) )
    437439    local_pf = 0.0
    438 !
    439 !-- Allocate temporary array used for exchanging ghoist points of surface-data
    440     ALLOCATE( tmp_2d(nysg:nyng,nxlg:nxrg) )
    441     tmp_2d = 0.0
    442440
    443441!
     
    481479             CASE ( 'lwp*_xy' )        ! 2d-array
    482480                IF ( av == 0 )  THEN
    483                    DO  i = nxlg, nxrg
    484                       DO  j = nysg, nyng
     481                   DO  i = nxl, nxr
     482                      DO  j = nys, nyn
    485483                         local_pf(i,j,nzb+1) = SUM( ql(nzb:nzt,j,i) *          &
    486484                                                    dzw(1:nzt+1) )
     
    488486                   ENDDO
    489487                ELSE
    490                    DO  i = nxlg, nxrg
    491                       DO  j = nysg, nyng
     488                   DO  i = nxl, nxr
     489                      DO  j = nys, nyn
    492490                         local_pf(i,j,nzb+1) = lwp_av(j,i)
    493491                      ENDDO
     
    519517                      i = surf_def_h(0)%i(m)
    520518                      j = surf_def_h(0)%j(m)
    521                       tmp_2d(j,i) = surf_def_h(0)%ol(m)
     519                      local_pf(i,j,nzb+1) = surf_def_h(0)%ol(m)
    522520                   ENDDO
    523521                   DO  m = 1, surf_lsm_h%ns
    524522                      i = surf_lsm_h%i(m)
    525523                      j = surf_lsm_h%j(m)
    526                       tmp_2d(j,i) = surf_lsm_h%ol(m)
     524                      local_pf(i,j,nzb+1) = surf_lsm_h%ol(m)
    527525                   ENDDO
    528526                   DO  m = 1, surf_usm_h%ns
    529527                      i = surf_usm_h%i(m)
    530528                      j = surf_usm_h%j(m)
    531                       tmp_2d(j,i) = surf_usm_h%ol(m)
    532                    ENDDO
    533 
    534                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    535 
    536                    DO  i = nxlg, nxrg
    537                       DO  j = nysg, nyng
    538                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    539                       ENDDO
    540                    ENDDO
    541 
    542                 ELSE
    543                    DO  i = nxlg, nxrg
    544                       DO  j = nysg, nyng
     529                      local_pf(i,j,nzb+1) = surf_usm_h%ol(m)
     530                   ENDDO
     531                ELSE
     532                   DO  i = nxl, nxr
     533                      DO  j = nys, nyn
    545534                         local_pf(i,j,nzb+1) = ol_av(j,i)
    546535                      ENDDO
     
    565554                   IF ( simulated_time >= particle_advection_start )  THEN
    566555                      tend = prt_count
    567                       CALL exchange_horiz( tend, nbgp )
     556!                      CALL exchange_horiz( tend, nbgp )
    568557                   ELSE
    569558                      tend = 0.0_wp
    570559                   ENDIF
    571                    DO  i = nxlg, nxrg
    572                       DO  j = nysg, nyng
     560                   DO  i = nxl, nxr
     561                      DO  j = nys, nyn
    573562                         DO  k = nzb, nzt+1
    574563                            local_pf(i,j,k) = tend(k,j,i)
     
    578567                   resorted = .TRUE.
    579568                ELSE
    580                    CALL exchange_horiz( pc_av, nbgp )
     569!                   CALL exchange_horiz( pc_av, nbgp )
    581570                   to_be_resorted => pc_av
    582571                ENDIF
     
    610599                         ENDDO
    611600                      ENDDO
    612                       CALL exchange_horiz( tend, nbgp )
     601!                      CALL exchange_horiz( tend, nbgp )
    613602                   ELSE
    614603                      tend = 0.0_wp
    615604                   ENDIF
    616                    DO  i = nxlg, nxrg
    617                       DO  j = nysg, nyng
     605                   DO  i = nxl, nxr
     606                      DO  j = nys, nyn
    618607                         DO  k = nzb, nzt+1
    619608                            local_pf(i,j,k) = tend(k,j,i)
     
    623612                   resorted = .TRUE.
    624613                ELSE
    625                    CALL exchange_horiz( pr_av, nbgp )
     614!                   CALL exchange_horiz( pr_av, nbgp )
    626615                   to_be_resorted => pr_av
    627616                ENDIF
    628617
    629618             CASE ( 'pra*_xy' )        ! 2d-array / integral quantity => no av
    630                 CALL exchange_horiz_2d( precipitation_amount )
    631                    DO  i = nxlg, nxrg
    632                       DO  j = nysg, nyng
     619!                CALL exchange_horiz_2d( precipitation_amount )
     620                   DO  i = nxl, nxr
     621                      DO  j = nys, nyn
    633622                      local_pf(i,j,nzb+1) =  precipitation_amount(j,i)
    634623                   ENDDO
     
    641630             CASE ( 'prr*_xy' )        ! 2d-array
    642631                IF ( av == 0 )  THEN
    643                    CALL exchange_horiz_2d( prr(nzb+1,:,:) )
    644                    DO  i = nxlg, nxrg
    645                       DO  j = nysg, nyng
     632!                   CALL exchange_horiz_2d( prr(nzb+1,:,:) )
     633                   DO  i = nxl, nxr
     634                      DO  j = nys, nyn
    646635                         local_pf(i,j,nzb+1) = prr(nzb+1,j,i) * hyrho(nzb+1)
    647636                      ENDDO
    648637                   ENDDO
    649638                ELSE
    650                    CALL exchange_horiz_2d( prr_av(nzb+1,:,:) )
    651                    DO  i = nxlg, nxrg
    652                       DO  j = nysg, nyng
     639!                   CALL exchange_horiz_2d( prr_av(nzb+1,:,:) )
     640                   DO  i = nxl, nxr
     641                      DO  j = nys, nyn
    653642                         local_pf(i,j,nzb+1) = prr_av(nzb+1,j,i) * hyrho(nzb+1)
    654643                      ENDDO
     
    661650             CASE ( 'prr_xy', 'prr_xz', 'prr_yz' )
    662651                IF ( av == 0 )  THEN
    663                    CALL exchange_horiz( prr, nbgp )
    664                    DO  i = nxlg, nxrg
    665                       DO  j = nysg, nyng
     652!                   CALL exchange_horiz( prr, nbgp )
     653                   DO  i = nxl, nxr
     654                      DO  j = nys, nyn
    666655                         DO  k = nzb, nzt+1
    667656                            local_pf(i,j,k) = prr(k,j,i) * hyrho(nzb+1)
     
    670659                   ENDDO
    671660                ELSE
    672                    CALL exchange_horiz( prr_av, nbgp )
    673                    DO  i = nxlg, nxrg
    674                       DO  j = nysg, nyng
     661!                   CALL exchange_horiz( prr_av, nbgp )
     662                   DO  i = nxl, nxr
     663                      DO  j = nys, nyn
    675664                         DO  k = nzb, nzt+1
    676665                            local_pf(i,j,k) = prr_av(k,j,i) * hyrho(nzb+1)
     
    687676                      to_be_resorted => pt
    688677                   ELSE
    689                    DO  i = nxlg, nxrg
    690                       DO  j = nysg, nyng
     678                   DO  i = nxl, nxr
     679                      DO  j = nys, nyn
    691680                            DO  k = nzb, nzt+1
    692681                               local_pf(i,j,k) = pt(k,j,i) + l_d_cp *          &
     
    762751                         ENDDO
    763752                      ENDDO
    764                       CALL exchange_horiz( tend, nbgp )
     753!                      CALL exchange_horiz( tend, nbgp )
    765754                   ELSE
    766755                      tend = 0.0_wp
    767756                   ENDIF
    768                    DO  i = nxlg, nxrg
    769                       DO  j = nysg, nyng
     757                   DO  i = nxl, nxr
     758                      DO  j = nys, nyn
    770759                         DO  k = nzb, nzt+1
    771760                            local_pf(i,j,k) = tend(k,j,i)
     
    775764                   resorted = .TRUE.
    776765                ELSE
    777                    CALL exchange_horiz( ql_vp_av, nbgp )
     766!                   CALL exchange_horiz( ql_vp_av, nbgp )
    778767                   to_be_resorted => ql_vp
    779768                ENDIF
     
    793782                      i = surf_def_h(0)%i(m)
    794783                      j = surf_def_h(0)%j(m)
    795                       tmp_2d(j,i) = surf_def_h(0)%qsws(m)
     784                      local_pf(i,j,nzb+1) = surf_def_h(0)%qsws(m)
    796785                   ENDDO
    797786                   DO  m = 1, surf_lsm_h%ns
    798787                      i = surf_lsm_h%i(m)
    799788                      j = surf_lsm_h%j(m)
    800                       tmp_2d(j,i) = surf_lsm_h%qsws(m)
     789                      local_pf(i,j,nzb+1) = surf_lsm_h%qsws(m)
    801790                   ENDDO
    802791                   DO  m = 1, surf_usm_h%ns
    803792                      i = surf_usm_h%i(m)
    804793                      j = surf_usm_h%j(m)
    805                       tmp_2d(j,i) = surf_usm_h%qsws(m)
    806                    ENDDO
    807 
    808                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    809 
    810                    DO  i = nxlg, nxrg
    811                       DO  j = nysg, nyng
    812                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    813                       ENDDO
    814                    ENDDO
    815                 ELSE
    816                    DO  i = nxlg, nxrg
    817                       DO  j = nysg, nyng
     794                      local_pf(i,j,nzb+1) = surf_usm_h%qsws(m)
     795                   ENDDO
     796                ELSE
     797                   DO  i = nxl, nxr
     798                      DO  j = nys, nyn
    818799                         local_pf(i,j,nzb+1) =  qsws_av(j,i)
    819800                      ENDDO
     
    826807             CASE ( 'qv_xy', 'qv_xz', 'qv_yz' )
    827808                IF ( av == 0 )  THEN
    828                    DO  i = nxlg, nxrg
    829                       DO  j = nysg, nyng
     809                   DO  i = nxl, nxr
     810                      DO  j = nys, nyn
    830811                         DO  k = nzb, nzt+1
    831812                            local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
     
    867848                      i = surf_def_h(0)%i(m)
    868849                      j = surf_def_h(0)%j(m)
    869                       tmp_2d(j,i) = surf_def_h(0)%shf(m)
     850                      local_pf(i,j,nzb+1) = surf_def_h(0)%shf(m)
    870851                   ENDDO
    871852                   DO  m = 1, surf_lsm_h%ns
    872853                      i = surf_lsm_h%i(m)
    873854                      j = surf_lsm_h%j(m)
    874                       tmp_2d(j,i) = surf_lsm_h%shf(m)
     855                      local_pf(i,j,nzb+1) = surf_lsm_h%shf(m)
    875856                   ENDDO
    876857                   DO  m = 1, surf_usm_h%ns
    877858                      i = surf_usm_h%i(m)
    878859                      j = surf_usm_h%j(m)
    879                       tmp_2d(j,i) = surf_usm_h%shf(m)
    880                    ENDDO
    881 
    882                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    883 
    884                    DO  i = nxlg, nxrg
    885                       DO  j = nysg, nyng
    886                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    887                       ENDDO
    888                    ENDDO
    889                 ELSE
    890                    DO  i = nxlg, nxrg
    891                       DO  j = nysg, nyng
     860                      local_pf(i,j,nzb+1) = surf_usm_h%shf(m)
     861                   ENDDO
     862                ELSE
     863                   DO  i = nxl, nxr
     864                      DO  j = nys, nyn
    892865                         local_pf(i,j,nzb+1) =  shf_av(j,i)
    893866                      ENDDO
     
    903876                      i = surf_def_h(0)%i(m)
    904877                      j = surf_def_h(0)%j(m)
    905                       tmp_2d(j,i) = surf_def_h(0)%ssws(m)
     878                      local_pf(i,j,nzb+1) = surf_def_h(0)%ssws(m)
    906879                   ENDDO
    907880                   DO  m = 1, surf_lsm_h%ns
    908881                      i = surf_lsm_h%i(m)
    909882                      j = surf_lsm_h%j(m)
    910                       tmp_2d(j,i) = surf_lsm_h%ssws(m)
     883                      local_pf(i,j,nzb+1) = surf_lsm_h%ssws(m)
    911884                   ENDDO
    912885                   DO  m = 1, surf_usm_h%ns
    913886                      i = surf_usm_h%i(m)
    914887                      j = surf_usm_h%j(m)
    915                       tmp_2d(j,i) = surf_usm_h%ssws(m)
    916                    ENDDO
    917 
    918                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    919 
    920                    DO  i = nxlg, nxrg
    921                       DO  j = nysg, nyng
    922                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    923                       ENDDO
    924                    ENDDO
    925                 ELSE
    926                    DO  i = nxlg, nxrg
    927                       DO  j = nysg, nyng
     888                      local_pf(i,j,nzb+1) = surf_usm_h%ssws(m)
     889                   ENDDO
     890                ELSE
     891                   DO  i = nxl, nxr
     892                      DO  j = nys, nyn
    928893                         local_pf(i,j,nzb+1) =  ssws_av(j,i)
    929894                      ENDDO
     
    939904                      i = surf_def_h(0)%i(m)
    940905                      j = surf_def_h(0)%j(m)
    941                       tmp_2d(j,i) = surf_def_h(0)%ts(m)
     906                      local_pf(i,j,nzb+1) = surf_def_h(0)%ts(m)
    942907                   ENDDO
    943908                   DO  m = 1, surf_lsm_h%ns
    944909                      i = surf_lsm_h%i(m)
    945910                      j = surf_lsm_h%j(m)
    946                       tmp_2d(j,i) = surf_lsm_h%ts(m)
     911                      local_pf(i,j,nzb+1) = surf_lsm_h%ts(m)
    947912                   ENDDO
    948913                   DO  m = 1, surf_usm_h%ns
    949914                      i = surf_usm_h%i(m)
    950915                      j = surf_usm_h%j(m)
    951                       tmp_2d(j,i) = surf_usm_h%ts(m)
    952                    ENDDO
    953 
    954                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    955 
    956                    DO  i = nxlg, nxrg
    957                       DO  j = nysg, nyng
    958                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    959                       ENDDO
    960                    ENDDO
    961 
    962                 ELSE
    963                    DO  i = nxlg, nxrg
    964                       DO  j = nysg, nyng
     916                      local_pf(i,j,nzb+1) = surf_usm_h%ts(m)
     917                   ENDDO
     918                ELSE
     919                   DO  i = nxl, nxr
     920                      DO  j = nys, nyn
    965921                         local_pf(i,j,nzb+1) = ts_av(j,i)
    966922                      ENDDO
     
    990946                      i = surf_def_h(0)%i(m)
    991947                      j = surf_def_h(0)%j(m)
    992                       tmp_2d(j,i) = surf_def_h(0)%us(m)
     948                      local_pf(i,j,nzb+1) = surf_def_h(0)%us(m)
    993949                   ENDDO
    994950                   DO  m = 1, surf_lsm_h%ns
    995951                      i = surf_lsm_h%i(m)
    996952                      j = surf_lsm_h%j(m)
    997                       tmp_2d(j,i) = surf_lsm_h%us(m)
     953                      local_pf(i,j,nzb+1) = surf_lsm_h%us(m)
    998954                   ENDDO
    999955                   DO  m = 1, surf_usm_h%ns
    1000956                      i = surf_usm_h%i(m)
    1001957                      j = surf_usm_h%j(m)
    1002                       tmp_2d(j,i) = surf_usm_h%us(m)
    1003                    ENDDO
    1004 
    1005                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    1006 
    1007                    DO  i = nxlg, nxrg
    1008                       DO  j = nysg, nyng
    1009                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    1010                       ENDDO
    1011                    ENDDO
    1012                 ELSE
    1013                    DO  i = nxlg, nxrg
    1014                       DO  j = nysg, nyng
     958                      local_pf(i,j,nzb+1) = surf_usm_h%us(m)
     959                   ENDDO
     960                ELSE
     961                   DO  i = nxl, nxr
     962                      DO  j = nys, nyn
    1015963                         local_pf(i,j,nzb+1) = us_av(j,i)
    1016964                      ENDDO
     
    10561004                      i = surf_def_h(0)%i(m)
    10571005                      j = surf_def_h(0)%j(m)
    1058                       tmp_2d(j,i) = surf_def_h(0)%z0(m)
     1006                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0(m)
    10591007                   ENDDO
    10601008                   DO  m = 1, surf_lsm_h%ns
    10611009                      i = surf_lsm_h%i(m)
    10621010                      j = surf_lsm_h%j(m)
    1063                       tmp_2d(j,i) = surf_lsm_h%z0(m)
     1011                      local_pf(i,j,nzb+1) = surf_lsm_h%z0(m)
    10641012                   ENDDO
    10651013                   DO  m = 1, surf_usm_h%ns
    10661014                      i = surf_usm_h%i(m)
    10671015                      j = surf_usm_h%j(m)
    1068                       tmp_2d(j,i) = surf_usm_h%z0(m)
    1069                    ENDDO
    1070 
    1071                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    1072 
    1073                    DO  i = nxlg, nxrg
    1074                       DO  j = nysg, nyng
    1075                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    1076                       ENDDO
    1077                    ENDDO
    1078 
    1079                 ELSE
    1080                    DO  i = nxlg, nxrg
    1081                       DO  j = nysg, nyng
     1016                      local_pf(i,j,nzb+1) = surf_usm_h%z0(m)
     1017                   ENDDO
     1018                ELSE
     1019                   DO  i = nxl, nxr
     1020                      DO  j = nys, nyn
    10821021                         local_pf(i,j,nzb+1) =  z0_av(j,i)
    10831022                      ENDDO
     
    10931032                      i = surf_def_h(0)%i(m)
    10941033                      j = surf_def_h(0)%j(m)
    1095                       tmp_2d(j,i) = surf_def_h(0)%z0h(m)
     1034                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0h(m)
    10961035                   ENDDO
    10971036                   DO  m = 1, surf_lsm_h%ns
    10981037                      i = surf_lsm_h%i(m)
    10991038                      j = surf_lsm_h%j(m)
    1100                       tmp_2d(j,i) = surf_lsm_h%z0h(m)
     1039                      local_pf(i,j,nzb+1) = surf_lsm_h%z0h(m)
    11011040                   ENDDO
    11021041                   DO  m = 1, surf_usm_h%ns
    11031042                      i = surf_usm_h%i(m)
    11041043                      j = surf_usm_h%j(m)
    1105                       tmp_2d(j,i) = surf_usm_h%z0h(m)
    1106                    ENDDO
    1107 
    1108                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    1109 
    1110                    DO  i = nxlg, nxrg
    1111                       DO  j = nysg, nyng
    1112                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    1113                       ENDDO
    1114                    ENDDO
    1115                 ELSE
    1116                    DO  i = nxlg, nxrg
    1117                       DO  j = nysg, nyng
     1044                      local_pf(i,j,nzb+1) = surf_usm_h%z0h(m)
     1045                   ENDDO
     1046                ELSE
     1047                   DO  i = nxl, nxr
     1048                      DO  j = nys, nyn
    11181049                         local_pf(i,j,nzb+1) =  z0h_av(j,i)
    11191050                      ENDDO
     
    11291060                      i = surf_def_h(0)%i(m)
    11301061                      j = surf_def_h(0)%j(m)
    1131                       tmp_2d(j,i) = surf_def_h(0)%z0q(m)
     1062                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0q(m)
    11321063                   ENDDO
    11331064                   DO  m = 1, surf_lsm_h%ns
    11341065                      i = surf_lsm_h%i(m)
    11351066                      j = surf_lsm_h%j(m)
    1136                       tmp_2d(j,i) = surf_lsm_h%z0q(m)
     1067                      local_pf(i,j,nzb+1) = surf_lsm_h%z0q(m)
    11371068                   ENDDO
    11381069                   DO  m = 1, surf_usm_h%ns
    11391070                      i = surf_usm_h%i(m)
    11401071                      j = surf_usm_h%j(m)
    1141                       tmp_2d(j,i) = surf_usm_h%z0q(m)
    1142                    ENDDO
    1143 
    1144                    CALL exchange_horiz_2d( tmp_2d, nbgp )
    1145 
    1146                    DO  i = nxlg, nxrg
    1147                       DO  j = nysg, nyng
    1148                          local_pf(i,j,nzb+1) = tmp_2d(j,i)
    1149                       ENDDO
    1150                    ENDDO
    1151                 ELSE
    1152                    DO  i = nxlg, nxrg
    1153                       DO  j = nysg, nyng
     1072                      local_pf(i,j,nzb+1) = surf_usm_h%z0q(m)
     1073                   ENDDO
     1074                ELSE
     1075                   DO  i = nxl, nxr
     1076                      DO  j = nys, nyn
    11541077                         local_pf(i,j,nzb+1) =  z0q_av(j,i)
    11551078                      ENDDO
     
    12061129!--       Resort the array to be output, if not done above
    12071130          IF ( .NOT. resorted )  THEN
    1208              DO  i = nxlg, nxrg
    1209                 DO  j = nysg, nyng
     1131             DO  i = nxl, nxr
     1132                DO  j = nys, nyn
    12101133                   DO  k = nzb_do, nzt_do
    12111134                      local_pf(i,j,k) = to_be_resorted(k,j,i)
     
    12691192!--                   Carry out the averaging (all data are on the PE)
    12701193                      DO  k = nzb_do, nzt_do
    1271                          DO  j = nysg, nyng
    1272                             DO  i = nxlg, nxrg
     1194                         DO  j = nys, nyn
     1195                            DO  i = nxl, nxr
    12731196                               local_2d(i,j) = local_2d(i,j) + local_pf(i,j,k)
    12741197                            ENDDO
     
    13001223!--                   here on a local array and will be written to the output
    13011224!--                   file afterwards to increase the performance.
    1302                       DO  i = nxlg, nxrg
    1303                          DO  j = nysg, nyng
     1225                      DO  i = nxl, nxr
     1226                         DO  j = nys, nyn
    13041227                            local_2d_sections(i,j,iis) = local_2d(i,j)
    13051228                         ENDDO
     
    13191242                         DO  i = 0, io_blocks-1
    13201243                            IF ( i == io_group )  THEN
    1321                                WRITE ( 21 )  nxlg, nxrg, nysg, nyng, nysg, nyng
     1244                               WRITE ( 21 )  nxl, nxr, nys, nyn, nys, nyn
    13221245                               WRITE ( 21 )  local_2d
    13231246                            ENDIF
     
    13351258                         CALL MPI_BARRIER( comm2d, ierr )
    13361259
    1337                          ngp = ( nxrg-nxlg+1 ) * ( nyng-nysg+1 )
     1260                         ngp = ( nxr-nxl+1 ) * ( nyn-nys+1 )
    13381261                         IF ( myid == 0 )  THEN
    13391262!
    13401263!--                         Local array can be relocated directly.
    1341                             total_2d(nxlg:nxrg,nysg:nyng) = local_2d
     1264                            total_2d(nxl:nxr,nys:nyn) = local_2d
    13421265!
    13431266!--                         Receive data from all other PEs.
     
    13611284!--                         Relocate the local array for the next loop increment
    13621285                            DEALLOCATE( local_2d )
    1363                             ALLOCATE( local_2d(nxlg:nxrg,nysg:nyng) )
     1286                            ALLOCATE( local_2d(nxl:nxr,nys:nyn) )
    13641287
    13651288#if defined( __netcdf )
     
    13671290                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
    13681291                                                       id_var_do2d(av,if),  &
    1369                                                    total_2d(0:nx+1,0:ny+1), &
     1292                                                       total_2d(0:nx,0:ny), &
    13701293                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
    1371                                              count = (/ nx+2, ny+2, 1, 1 /) )
     1294                                             count = (/ nx+1, ny+1, 1, 1 /) )
    13721295                            ELSE
    13731296                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
    13741297                                                       id_var_do2d(av,if),  &
    1375                                                    total_2d(0:nx+1,0:ny+1), &
     1298                                                       total_2d(0:nx,0:ny), &
    13761299                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
    1377                                              count = (/ nx+2, ny+2, 1, 1 /) )
     1300                                             count = (/ nx+1, ny+1, 1, 1 /) )
    13781301                            ENDIF
    13791302                            CALL netcdf_handle_error( 'data_output_2d', 54 )
     
    13831306!
    13841307!--                         First send the local index limits to PE0
    1385                             ind(1) = nxlg; ind(2) = nxrg
    1386                             ind(3) = nysg; ind(4) = nyng
     1308                            ind(1) = nxl; ind(2) = nxr
     1309                            ind(3) = nys; ind(4) = nyn
    13871310                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
    13881311                                           comm2d, ierr )
    13891312!
    13901313!--                         Send data to PE0
    1391                             CALL MPI_SEND( local_2d(nxlg,nysg), ngp,           &
     1314                            CALL MPI_SEND( local_2d(nxl,nys), ngp,             &
    13921315                                           MPI_REAL, 0, 1, comm2d, ierr )
    13931316                         ENDIF
     
    14051328                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    14061329                                              id_var_do2d(av,if),           &
    1407                                              local_2d(nxl:nxr+1,nys:nyn+1), &
     1330                                              local_2d(nxl:nxr,nys:nyn),    &
    14081331                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
    1409                                            count = (/ nx+2, ny+2, 1, 1 /) )
     1332                                           count = (/ nx+1, ny+1, 1, 1 /) )
    14101333                   ELSE
    14111334                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    14121335                                              id_var_do2d(av,if),           &
    1413                                              local_2d(nxl:nxr+1,nys:nyn+1), &
     1336                                              local_2d(nxl:nxr,nys:nyn),    &
    14141337                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
    1415                                            count = (/ nx+2, ny+2, 1, 1 /) )
     1338                                           count = (/ nx+1, ny+1, 1, 1 /) )
    14161339                   ENDIF
    14171340                   CALL netcdf_handle_error( 'data_output_2d', 447 )
     
    14551378                   IF ( section(is,s_ind) == -1 )  THEN
    14561379
    1457                       ALLOCATE( local_2d_l(nxlg:nxrg,nzb_do:nzt_do) )
     1380                      ALLOCATE( local_2d_l(nxl:nxr,nzb_do:nzt_do) )
    14581381                      local_2d_l = 0.0_wp
    1459                       ngp = ( nxrg-nxlg + 1 ) * ( nzt_do-nzb_do + 1 )
     1382                      ngp = ( nxr-nxl + 1 ) * ( nzt_do-nzb_do + 1 )
    14601383!
    14611384!--                   First local averaging on the PE
    14621385                      DO  k = nzb_do, nzt_do
    14631386                         DO  j = nys, nyn
    1464                             DO  i = nxlg, nxrg
     1387                            DO  i = nxl, nxr
    14651388                               local_2d_l(i,k) = local_2d_l(i,k) +             &
    14661389                                                 local_pf(i,j,k)
     
    14721395!--                   Now do the averaging over all PEs along y
    14731396                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1474                       CALL MPI_ALLREDUCE( local_2d_l(nxlg,nzb_do),                &
    1475                                           local_2d(nxlg,nzb_do), ngp, MPI_REAL,   &
     1397                      CALL MPI_ALLREDUCE( local_2d_l(nxl,nzb_do),                &
     1398                                          local_2d(nxl,nzb_do), ngp, MPI_REAL,   &
    14761399                                          MPI_SUM, comm1dy, ierr )
    14771400#else
     
    15081431!--                      stored here on a local array and will be written to the
    15091432!--                      output file afterwards to increase the performance.
    1510                          DO  i = nxlg, nxrg
     1433                         DO  i = nxl, nxr
    15111434                            DO  k = nzb_do, nzt_do
    15121435                               local_2d_sections_l(i,is,k) = local_2d(i,k)
     
    15361459                                      nys-1 == -1 ) )                          &
    15371460                               THEN
    1538                                   WRITE (22)  nxlg, nxrg, nzb_do, nzt_do, nzb, nzt+1
     1461                                  WRITE (22)  nxl, nxr, nzb_do, nzt_do, nzb, nzt+1
    15391462                                  WRITE (22)  local_2d
    15401463                               ELSE
     
    15551478                         CALL MPI_BARRIER( comm2d, ierr )
    15561479
    1557                          ngp = ( nxrg-nxlg + 1 ) * ( nzt_do-nzb_do + 1 )
     1480                         ngp = ( nxr-nxl + 1 ) * ( nzt_do-nzb_do + 1 )
    15581481                         IF ( myid == 0 )  THEN
    15591482!
     
    15631486                                 ( section(is,s_ind) == -1  .AND.               &
    15641487                                   nys-1 == -1 ) )  THEN
    1565                                total_2d(nxlg:nxrg,nzb_do:nzt_do) = local_2d
     1488                               total_2d(nxl:nxr,nzb_do:nzt_do) = local_2d
    15661489                            ENDIF
    15671490!
     
    15921515!--                         Relocate the local array for the next loop increment
    15931516                            DEALLOCATE( local_2d )
    1594                             ALLOCATE( local_2d(nxlg:nxrg,nzb_do:nzt_do) )
     1517                            ALLOCATE( local_2d(nxl:nxr,nzb_do:nzt_do) )
    15951518
    15961519#if defined( __netcdf )
    1597                             nc_stat = NF90_PUT_VAR( id_set_xz(av),          &
    1598                                                  id_var_do2d(av,if),        &
    1599                                                  total_2d(0:nx+1,nzb_do:nzt_do),&
    1600                             start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
    1601                                              count = (/ nx+2, 1, nzt_do-nzb_do+1, 1 /) )
     1520                            nc_stat = NF90_PUT_VAR( id_set_xz(av),             &
     1521                                                 id_var_do2d(av,if),           &
     1522                                                 total_2d(0:nx,nzb_do:nzt_do), &
     1523                               start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
     1524                                          count = (/ nx+1, 1, nzt_do-nzb_do+1, 1 /) )
    16021525                            CALL netcdf_handle_error( 'data_output_2d', 58 )
    16031526#endif
     
    16111534                                 ( section(is,s_ind) == -1  .AND.  nys-1 == -1 ) ) &
    16121535                            THEN
    1613                                ind(1) = nxlg; ind(2) = nxrg
     1536                               ind(1) = nxl; ind(2) = nxr
    16141537                               ind(3) = nzb_do;   ind(4) = nzt_do
    16151538                            ELSE
     
    16221545!--                         If applicable, send data to PE0.
    16231546                            IF ( ind(1) /= -9999 )  THEN
    1624                                CALL MPI_SEND( local_2d(nxlg,nzb_do), ngp,         &
     1547                               CALL MPI_SEND( local_2d(nxl,nzb_do), ngp,         &
    16251548                                              MPI_REAL, 0, 1, comm2d, ierr )
    16261549                            ENDIF
     
    16381561                   nc_stat = NF90_PUT_VAR( id_set_xz(av),                   &
    16391562                                           id_var_do2d(av,if),              &
    1640                                            local_2d(nxl:nxr+1,nzb_do:nzt_do),  &
     1563                                           local_2d(nxl:nxr,nzb_do:nzt_do), &
    16411564                            start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
    1642                                            count = (/ nx+2, 1, nzt_do-nzb_do+1, 1 /) )
     1565                                       count = (/ nx+1, 1, nzt_do-nzb_do+1, 1 /) )
    16431566                   CALL netcdf_handle_error( 'data_output_2d', 451 )
    16441567#endif
     
    16731596                   IF ( section(is,s_ind) == -1 )  THEN
    16741597
    1675                       ALLOCATE( local_2d_l(nysg:nyng,nzb_do:nzt_do) )
     1598                      ALLOCATE( local_2d_l(nys:nyn,nzb_do:nzt_do) )
    16761599                      local_2d_l = 0.0_wp
    1677                       ngp = ( nyng-nysg+1 ) * ( nzt_do-nzb_do+1 )
     1600                      ngp = ( nyn-nys+1 ) * ( nzt_do-nzb_do+1 )
    16781601!
    16791602!--                   First local averaging on the PE
    16801603                      DO  k = nzb_do, nzt_do
    1681                          DO  j = nysg, nyng
     1604                         DO  j = nys, nyn
    16821605                            DO  i = nxl, nxr
    16831606                               local_2d_l(j,k) = local_2d_l(j,k) +             &
     
    16901613!--                   Now do the averaging over all PEs along x
    16911614                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1692                       CALL MPI_ALLREDUCE( local_2d_l(nysg,nzb_do),                &
    1693                                           local_2d(nysg,nzb_do), ngp, MPI_REAL,   &
     1615                      CALL MPI_ALLREDUCE( local_2d_l(nys,nzb_do),                &
     1616                                          local_2d(nys,nzb_do), ngp, MPI_REAL,   &
    16941617                                          MPI_SUM, comm1dx, ierr )
    16951618#else
     
    17261649!--                      stored here on a local array and will be written to the
    17271650!--                      output file afterwards to increase the performance.
    1728                          DO  j = nysg, nyng
     1651                         DO  j = nys, nyn
    17291652                            DO  k = nzb_do, nzt_do
    17301653                               local_2d_sections_l(is,j,k) = local_2d(j,k)
     
    17541677                                      nxl-1 == -1 ) )                          &
    17551678                               THEN
    1756                                   WRITE (23)  nysg, nyng, nzb_do, nzt_do, nzb, nzt+1
     1679                                  WRITE (23)  nys, nyn, nzb_do, nzt_do, nzb, nzt+1
    17571680                                  WRITE (23)  local_2d
    17581681                               ELSE
     
    17731696                         CALL MPI_BARRIER( comm2d, ierr )
    17741697
    1775                          ngp = ( nyng-nysg+1 ) * ( nzt_do-nzb_do+1 )
     1698                         ngp = ( nyn-nys+1 ) * ( nzt_do-nzb_do+1 )
    17761699                         IF ( myid == 0 )  THEN
    17771700!
     
    17811704                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
    17821705                            THEN
    1783                                total_2d(nysg:nyng,nzb_do:nzt_do) = local_2d
     1706                               total_2d(nys:nyn,nzb_do:nzt_do) = local_2d
    17841707                            ENDIF
    17851708!
     
    18101733!--                         Relocate the local array for the next loop increment
    18111734                            DEALLOCATE( local_2d )
    1812                             ALLOCATE( local_2d(nysg:nyng,nzb_do:nzt_do) )
     1735                            ALLOCATE( local_2d(nys:nyn,nzb_do:nzt_do) )
    18131736
    18141737#if defined( __netcdf )
    1815                             nc_stat = NF90_PUT_VAR( id_set_yz(av),          &
    1816                                                  id_var_do2d(av,if),        &
    1817                                                  total_2d(0:ny+1,nzb_do:nzt_do),&
    1818                             start = (/ is, 1, 1, do2d_yz_time_count(av) /), &
    1819                                              count = (/ 1, ny+2, nzt_do-nzb_do+1, 1 /) )
     1738                            nc_stat = NF90_PUT_VAR( id_set_yz(av),             &
     1739                                                 id_var_do2d(av,if),           &
     1740                                                 total_2d(0:ny,nzb_do:nzt_do), &
     1741                            start = (/ is, 1, 1, do2d_yz_time_count(av) /),    &
     1742                                       count = (/ 1, ny+1, nzt_do-nzb_do+1, 1 /) )
    18201743                            CALL netcdf_handle_error( 'data_output_2d', 61 )
    18211744#endif
     
    18291752                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
    18301753                            THEN
    1831                                ind(1) = nysg; ind(2) = nyng
     1754                               ind(1) = nys; ind(2) = nyn
    18321755                               ind(3) = nzb_do;   ind(4) = nzt_do
    18331756                            ELSE
     
    18401763!--                         If applicable, send data to PE0.
    18411764                            IF ( ind(1) /= -9999 )  THEN
    1842                                CALL MPI_SEND( local_2d(nysg,nzb_do), ngp,         &
     1765                               CALL MPI_SEND( local_2d(nys,nzb_do), ngp,         &
    18431766                                              MPI_REAL, 0, 1, comm2d, ierr )
    18441767                            ENDIF
     
    18561779                   nc_stat = NF90_PUT_VAR( id_set_yz(av),                   &
    18571780                                           id_var_do2d(av,if),              &
    1858                                            local_2d(nys:nyn+1,nzb_do:nzt_do),  &
     1781                                           local_2d(nys:nyn,nzb_do:nzt_do), &
    18591782                            start = (/ is, 1, 1, do2d_xz_time_count(av) /), &
    1860                                            count = (/ 1, ny+2, nzt_do-nzb_do+1, 1 /) )
     1783                                           count = (/ 1, ny+1, nzt_do-nzb_do+1, 1 /) )
    18611784                   CALL netcdf_handle_error( 'data_output_2d', 452 )
    18621785#endif
     
    18871810!--                   Do not output redundant ghost point data except for the
    18881811!--                   boundaries of the total domain.
    1889                       IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    1890                          nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    1891                                                  id_var_do2d(av,if),           &
    1892                                                  local_2d_sections(nxl:nxr+1,  &
    1893                                                     nys:nyn,1:nis),            &
    1894                                                  start = (/ nxl+1, nys+1, 1,   &
    1895                                                     do2d_xy_time_count(av) /), &
    1896                                                  count = (/ nxr-nxl+2,         &
    1897                                                             nyn-nys+1, nis, 1  &
    1898                                                           /) )
    1899                       ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    1900                          nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    1901                                                  id_var_do2d(av,if),           &
    1902                                                  local_2d_sections(nxl:nxr,    &
    1903                                                     nys:nyn+1,1:nis),          &
    1904                                                  start = (/ nxl+1, nys+1, 1,   &
    1905                                                     do2d_xy_time_count(av) /), &
    1906                                                  count = (/ nxr-nxl+1,         &
    1907                                                             nyn-nys+2, nis, 1  &
    1908                                                           /) )
    1909                       ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    1910                          nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    1911                                                  id_var_do2d(av,if),           &
    1912                                                  local_2d_sections(nxl:nxr+1,  &
    1913                                                     nys:nyn+1,1:nis),          &
    1914                                                  start = (/ nxl+1, nys+1, 1,   &
    1915                                                     do2d_xy_time_count(av) /), &
    1916                                                  count = (/ nxr-nxl+2,         &
    1917                                                             nyn-nys+2, nis, 1  &
    1918                                                           /) )
    1919                       ELSE
     1812!                      IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     1813!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
     1814!                                                 id_var_do2d(av,if),           &
     1815!                                                 local_2d_sections(nxl:nxr+1,  &
     1816!                                                    nys:nyn,1:nis),            &
     1817!                                                 start = (/ nxl+1, nys+1, 1,   &
     1818!                                                    do2d_xy_time_count(av) /), &
     1819!                                                 count = (/ nxr-nxl+2,         &
     1820!                                                            nyn-nys+1, nis, 1  &
     1821!                                                          /) )
     1822!                      ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     1823!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
     1824!                                                 id_var_do2d(av,if),           &
     1825!                                                 local_2d_sections(nxl:nxr,    &
     1826!                                                    nys:nyn+1,1:nis),          &
     1827!                                                 start = (/ nxl+1, nys+1, 1,   &
     1828!                                                    do2d_xy_time_count(av) /), &
     1829!                                                 count = (/ nxr-nxl+1,         &
     1830!                                                            nyn-nys+2, nis, 1  &
     1831!                                                          /) )
     1832!                      ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     1833!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
     1834!                                                 id_var_do2d(av,if),           &
     1835!                                                 local_2d_sections(nxl:nxr+1,  &
     1836!                                                    nys:nyn+1,1:nis),          &
     1837!                                                 start = (/ nxl+1, nys+1, 1,   &
     1838!                                                    do2d_xy_time_count(av) /), &
     1839!                                                 count = (/ nxr-nxl+2,         &
     1840!                                                            nyn-nys+2, nis, 1  &
     1841!                                                          /) )
     1842!                      ELSE
    19201843                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    19211844                                                 id_var_do2d(av,if),           &
     
    19271850                                                            nyn-nys+1, nis, 1  &
    19281851                                                          /) )
    1929                       ENDIF   
     1852!                      ENDIF   
    19301853
    19311854                      CALL netcdf_handle_error( 'data_output_2d', 55 )
     
    19461869!
    19471870!--                      Distribute data over all PEs along y
    1948                          ngp = ( nxrg-nxlg+1 ) * ( nzt_do-nzb_do+1 ) * ns
     1871                         ngp = ( nxr-nxl+1 ) * ( nzt_do-nzb_do+1 ) * ns
    19491872                         IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr )
    1950                          CALL MPI_ALLREDUCE( local_2d_sections_l(nxlg,1,nzb_do),  &
    1951                                              local_2d_sections(nxlg,1,nzb_do),    &
     1873                         CALL MPI_ALLREDUCE( local_2d_sections_l(nxl,1,nzb_do),  &
     1874                                             local_2d_sections(nxl,1,nzb_do),    &
    19521875                                             ngp, MPI_REAL, MPI_SUM, comm1dy,  &
    19531876                                             ierr )
     
    19591882!--                   Do not output redundant ghost point data except for the
    19601883!--                   boundaries of the total domain.
    1961                       IF ( nxr == nx )  THEN
    1962                          nc_stat = NF90_PUT_VAR( id_set_xz(av),                &
    1963                                              id_var_do2d(av,if),               &
    1964                                              local_2d_sections(nxl:nxr+1,1:ns, &
    1965                                                 nzb_do:nzt_do),                &
    1966                                              start = (/ nxl+1, 1, 1,           &
    1967                                                 do2d_xz_time_count(av) /),     &
    1968                                              count = (/ nxr-nxl+2, ns, nzt_do-nzb_do+1,  &
    1969                                                         1 /) )
    1970                       ELSE
     1884!                      IF ( nxr == nx )  THEN
     1885!                         nc_stat = NF90_PUT_VAR( id_set_xz(av),                &
     1886!                                             id_var_do2d(av,if),               &
     1887!                                             local_2d_sections(nxl:nxr+1,1:ns, &
     1888!                                                nzb_do:nzt_do),                &
     1889!                                             start = (/ nxl+1, 1, 1,           &
     1890!                                                do2d_xz_time_count(av) /),     &
     1891!                                             count = (/ nxr-nxl+2, ns, nzt_do-nzb_do+1,  &
     1892!                                                        1 /) )
     1893!                      ELSE
    19711894                         nc_stat = NF90_PUT_VAR( id_set_xz(av),                &
    19721895                                             id_var_do2d(av,if),               &
     
    19771900                                             count = (/ nxr-nxl+1, ns, nzt_do-nzb_do+1,  &
    19781901                                                1 /) )
    1979                       ENDIF
     1902!                      ENDIF
    19801903
    19811904                      CALL netcdf_handle_error( 'data_output_2d', 57 )
     
    19961919!
    19971920!--                      Distribute data over all PEs along x
    1998                          ngp = ( nyng-nysg+1 ) * ( nzt-nzb + 2 ) * ns
     1921                         ngp = ( nyn-nys+1 ) * ( nzt-nzb + 2 ) * ns
    19991922                         IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr )
    2000                          CALL MPI_ALLREDUCE( local_2d_sections_l(1,nysg,nzb_do),  &
    2001                                              local_2d_sections(1,nysg,nzb_do),    &
     1923                         CALL MPI_ALLREDUCE( local_2d_sections_l(1,nys,nzb_do),  &
     1924                                             local_2d_sections(1,nys,nzb_do),    &
    20021925                                             ngp, MPI_REAL, MPI_SUM, comm1dx,  &
    20031926                                             ierr )
     
    20091932!--                   Do not output redundant ghost point data except for the
    20101933!--                   boundaries of the total domain.
    2011                       IF ( nyn == ny )  THEN
    2012                          nc_stat = NF90_PUT_VAR( id_set_yz(av),                &
    2013                                              id_var_do2d(av,if),               &
    2014                                              local_2d_sections(1:ns,           &
    2015                                                 nys:nyn+1,nzb_do:nzt_do),      &
    2016                                              start = (/ 1, nys+1, 1,           &
    2017                                                 do2d_yz_time_count(av) /),     &
    2018                                              count = (/ ns, nyn-nys+2,         &
    2019                                                         nzt_do-nzb_do+1, 1 /) )
    2020                       ELSE
     1934!                      IF ( nyn == ny )  THEN
     1935!                         nc_stat = NF90_PUT_VAR( id_set_yz(av),                &
     1936!                                             id_var_do2d(av,if),               &
     1937!                                             local_2d_sections(1:ns,           &
     1938!                                                nys:nyn+1,nzb_do:nzt_do),      &
     1939!                                             start = (/ 1, nys+1, 1,           &
     1940!                                                do2d_yz_time_count(av) /),     &
     1941!                                             count = (/ ns, nyn-nys+2,         &
     1942!                                                        nzt_do-nzb_do+1, 1 /) )
     1943!                      ELSE
    20211944                         nc_stat = NF90_PUT_VAR( id_set_yz(av),                &
    20221945                                             id_var_do2d(av,if),               &
     
    20271950                                             count = (/ ns, nyn-nys+1,         &
    20281951                                                        nzt_do-nzb_do+1, 1 /) )
    2029                       ENDIF
     1952!                      ENDIF
    20301953
    20311954                      CALL netcdf_handle_error( 'data_output_2d', 60 )
  • palm/trunk/SOURCE/data_output_3d.f90

    r2292 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29!
     30! 2292 2017-06-20 09:51:42Z schwenkel
    2731! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
    2832! includes two more prognostic equations for cloud drop concentration (nc) 
     
    178182       
    179183    USE indices,                                                               &
    180         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb
     184        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
    181185       
    182186    USE kinds
     
    241245!
    242246!-- Open output file.
    243 !-- Also creates coordinate and fld-file for AVS.
    244 !-- For classic or 64bit netCDF output or output of other (old) data formats,
    245 !-- for a run on more than one PE, each PE opens its own file and
    246 !-- writes the data of its subdomain in binary format (regardless of the format
    247 !-- the user has requested). After the run, these files are combined to one
    248 !-- file by combine_plot_fields in the format requested by the user (netcdf
    249 !-- and/or avs).
     247!-- For classic or 64bit netCDF output on more than one PE, each PE opens its
     248!-- own file and writes the data of its subdomain in binary format. After the
     249!-- run, these files are combined to one NetCDF file by combine_plot_fields.
    250250!-- For netCDF4/HDF5 output, data is written in parallel into one file.
    251251    IF ( netcdf_data_format < 5 )  THEN
     
    314314!
    315315!--    Allocate a temporary array with the desired output dimensions.
    316        ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) )
     316       ALLOCATE( local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do) )
    317317
    318318       SELECT CASE ( trimvar )
     
    359359                IF ( simulated_time >= particle_advection_start )  THEN
    360360                   tend = prt_count
    361                    CALL exchange_horiz( tend, nbgp )
    362361                ELSE
    363362                   tend = 0.0_wp
    364363                ENDIF
    365                 DO  i = nxlg, nxrg
    366                    DO  j = nysg, nyng
     364                DO  i = nxl, nxr
     365                   DO  j = nys, nyn
    367366                      DO  k = nzb_do, nzt_do
    368367                         local_pf(i,j,k) = tend(k,j,i)
     
    372371                resorted = .TRUE.
    373372             ELSE
    374                 CALL exchange_horiz( pc_av, nbgp )
    375373                to_be_resorted => pc_av
    376374             ENDIF
     
    404402                      ENDDO
    405403                   ENDDO
    406                    CALL exchange_horiz( tend, nbgp )
    407404                ELSE
    408405                   tend = 0.0_wp
    409406                ENDIF
    410                 DO  i = nxlg, nxrg
    411                    DO  j = nysg, nyng
     407                DO  i = nxl, nxr
     408                   DO  j = nys, nyn
    412409                      DO  k = nzb_do, nzt_do
    413410                         local_pf(i,j,k) = tend(k,j,i)
     
    417414                resorted = .TRUE.
    418415             ELSE
    419                 CALL exchange_horiz( pr_av, nbgp )
    420416                to_be_resorted => pr_av
    421417             ENDIF
     
    423419          CASE ( 'prr' )
    424420             IF ( av == 0 )  THEN
    425                 CALL exchange_horiz( prr, nbgp )
    426                 DO  i = nxlg, nxrg
    427                    DO  j = nysg, nyng
     421                DO  i = nxl, nxr
     422                   DO  j = nys, nyn
    428423                      DO  k = nzb_do, nzt_do
    429424                         local_pf(i,j,k) = prr(k,j,i)
     
    432427                ENDDO
    433428             ELSE
    434                 CALL exchange_horiz( prr_av, nbgp )
    435                 DO  i = nxlg, nxrg
    436                    DO  j = nysg, nyng
     429                DO  i = nxl, nxr
     430                   DO  j = nys, nyn
    437431                      DO  k = nzb_do, nzt_do
    438432                         local_pf(i,j,k) = prr_av(k,j,i)
     
    448442                   to_be_resorted => pt
    449443                ELSE
    450                    DO  i = nxlg, nxrg
    451                       DO  j = nysg, nyng
     444                   DO  i = nxl, nxr
     445                      DO  j = nys, nyn
    452446                         DO  k = nzb_do, nzt_do
    453447                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp *             &
     
    517511                      ENDDO
    518512                   ENDDO
    519                    CALL exchange_horiz( tend, nbgp )
    520513                ELSE
    521514                   tend = 0.0_wp
    522515                ENDIF
    523                 DO  i = nxlg, nxrg
    524                    DO  j = nysg, nyng
     516                DO  i = nxl, nxr
     517                   DO  j = nys, nyn
    525518                      DO  k = nzb_do, nzt_do
    526519                         local_pf(i,j,k) = tend(k,j,i)
     
    530523                resorted = .TRUE.
    531524             ELSE
    532                 CALL exchange_horiz( ql_vp_av, nbgp )
    533525                to_be_resorted => ql_vp_av
    534526             ENDIF
     
    543535          CASE ( 'qv' )
    544536             IF ( av == 0 )  THEN
    545                 DO  i = nxlg, nxrg
    546                    DO  j = nysg, nyng
     537                DO  i = nxl, nxr
     538                   DO  j = nys, nyn
    547539                      DO  k = nzb_do, nzt_do
    548540                         local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
     
    620612
    621613                DEALLOCATE ( local_pf )
    622                 ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) )
     614                ALLOCATE( local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do) )
    623615
    624616                CALL lsm_data_output_3d( av, do3d(av,if), found, local_pf )
     
    632624
    633625                   DEALLOCATE ( local_pf )
    634                    ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) )                 
     626                   ALLOCATE( local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do) )                 
    635627                ENDIF
    636628
     
    672664!--    Resort the array to be output, if not done above
    673665       IF ( .NOT. resorted )  THEN
    674           DO  i = nxlg, nxrg
    675              DO  j = nysg, nyng
     666          DO  i = nxl, nxr
     667             DO  j = nys, nyn
    676668                DO  k = nzb_do, nzt_do
    677669                   local_pf(i,j,k) = to_be_resorted(k,j,i)
     
    695687          DO  i = 0, io_blocks-1
    696688             IF ( i == io_group )  THEN
    697                 WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb_do, nzt_do
     689                WRITE ( 30 )  nxl, nxr, nys, nyn, nzb_do, nzt_do
    698690                WRITE ( 30 )  local_pf(:,:,nzb_do:nzt_do)
    699691             ENDIF
     
    707699!
    708700!--       Parallel output in netCDF4/HDF5 format.
    709 !--       Do not output redundant ghost point data except for the
    710 !--       boundaries of the total domain.
    711           IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    712              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    713                                local_pf(nxl:nxr+1,nys:nyn,nzb_do:nzt_do),    &
    714                 start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
    715                 count = (/ nxr-nxl+2, nyn-nys+1, nzt_do-nzb_do+1, 1 /) )
    716           ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    717              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    718                                local_pf(nxl:nxr,nys:nyn+1,nzb_do:nzt_do),    &
    719                 start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
    720                 count = (/ nxr-nxl+1, nyn-nys+2, nzt_do-nzb_do+1, 1 /) )
    721           ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    722              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    723                              local_pf(nxl:nxr+1,nys:nyn+1,nzb_do:nzt_do  ),  &
    724                 start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
    725                 count = (/ nxr-nxl+2, nyn-nys+2, nzt_do-nzb_do+1, 1 /) )
    726           ELSE
     701!          IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     702!             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     703!                               local_pf(nxl:nxr+1,nys:nyn,nzb_do:nzt_do),    &
     704!                start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
     705!                count = (/ nxr-nxl+2, nyn-nys+1, nzt_do-nzb_do+1, 1 /) )
     706!          ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     707!             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     708!                               local_pf(nxl:nxr,nys:nyn+1,nzb_do:nzt_do),    &
     709!                start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
     710!                count = (/ nxr-nxl+1, nyn-nys+2, nzt_do-nzb_do+1, 1 /) )
     711!          ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     712!             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     713!                             local_pf(nxl:nxr+1,nys:nyn+1,nzb_do:nzt_do  ),  &
     714!                start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
     715!                count = (/ nxr-nxl+2, nyn-nys+2, nzt_do-nzb_do+1, 1 /) )
     716!          ELSE
    727717             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    728718                                 local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do),    &
    729719                start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /),  &
    730720                count = (/ nxr-nxl+1, nyn-nys+1, nzt_do-nzb_do+1, 1 /) )
    731           ENDIF
     721!          ENDIF
    732722          CALL netcdf_handle_error( 'data_output_3d', 386 )
    733723#endif
     
    738728                         local_pf(nxl:nxr+1,nys:nyn+1,nzb_do:nzt_do),        &
    739729                         start = (/ 1, 1, 1, do3d_time_count(av) /),     &
    740                          count = (/ nx+2, ny+2, nzt_do-nzb_do+1, 1 /) )
     730                         count = (/ nx+1, ny+1, nzt_do-nzb_do+1, 1 /) )
    741731       CALL netcdf_handle_error( 'data_output_3d', 446 )
    742732#endif
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r2504 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29!
     30! 2504 2017-09-27 10:36:13Z maronga
    2731! Support roots and water under pavement. Added several pavement types.
    2832!
     
    38863890    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    38873891
    3888     REAL(wp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nzt+1) ::  local_pf !<
     3892    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
    38893893
    38903894
     
    39033907             ENDDO
    39043908          ELSE
    3905              DO  i = nxlg, nxrg
    3906                 DO  j = nysg, nyng
     3909             DO  i = nxl, nxr
     3910                DO  j = nys, nyn
    39073911                   local_pf(i,j,nzb+1) = c_liq_av(j,i)
    39083912                ENDDO
     
    39213925             ENDDO
    39223926          ELSE
    3923              DO  i = nxlg, nxrg
    3924                 DO  j = nysg, nyng
     3927             DO  i = nxl, nxr
     3928                DO  j = nys, nyn
    39253929                   local_pf(i,j,nzb+1) = c_soil_av(j,i)
    39263930                ENDDO
     
    39393943             ENDDO
    39403944          ELSE
    3941              DO  i = nxlg, nxrg
    3942                 DO  j = nysg, nyng
     3945             DO  i = nxl, nxr
     3946                DO  j = nys, nyn
    39433947                   local_pf(i,j,nzb+1) = c_veg_av(j,i)
    39443948                ENDDO
     
    39573961             ENDDO
    39583962          ELSE
    3959              DO  i = nxlg, nxrg
    3960                 DO  j = nysg, nyng
     3963             DO  i = nxl, nxr
     3964                DO  j = nys, nyn
    39613965                   local_pf(i,j,nzb+1) = ghf_av(j,i)
    39623966                ENDDO
     
    39753979             ENDDO
    39763980          ELSE
    3977              DO  i = nxlg, nxrg
    3978                 DO  j = nysg, nyng
     3981             DO  i = nxl, nxr
     3982                DO  j = nys, nyn
    39793983                   local_pf(i,j,nzb+1) = lai_av(j,i)
    39803984                ENDDO
     
    39933997             ENDDO
    39943998          ELSE
    3995              DO  i = nxlg, nxrg
    3996                 DO  j = nysg, nyng
     3999             DO  i = nxl, nxr
     4000                DO  j = nys, nyn
    39974001                   local_pf(i,j,nzb+1) = m_liq_av(j,i)
    39984002                ENDDO
     
    40134017             ENDDO
    40144018          ELSE
    4015              DO  i = nxlg, nxrg
    4016                 DO  j = nysg, nyng
     4019             DO  i = nxl, nxr
     4020                DO  j = nys, nyn
    40174021                   DO k = nzb_soil, nzt_soil
    40184022                      local_pf(i,j,k) = m_soil_av(k,j,i)
     
    40354039             ENDDO
    40364040          ELSE
    4037              DO  i = nxlg, nxrg
    4038                 DO  j = nysg, nyng
     4041             DO  i = nxl, nxr
     4042                DO  j = nys, nyn
    40394043                   local_pf(i,j,nzb+1) =  qsws_liq_av(j,i)
    40404044                ENDDO
     
    40534057             ENDDO
    40544058          ELSE
    4055              DO  i = nxlg, nxrg
    4056                 DO  j = nysg, nyng
     4059             DO  i = nxl, nxr
     4060                DO  j = nys, nyn
    40574061                   local_pf(i,j,nzb+1) =  qsws_soil_av(j,i)
    40584062                ENDDO
     
    40714075             ENDDO
    40724076          ELSE
    4073              DO  i = nxlg, nxrg
    4074                 DO  j = nysg, nyng
     4077             DO  i = nxl, nxr
     4078                DO  j = nys, nyn
    40754079                   local_pf(i,j,nzb+1) =  qsws_veg_av(j,i)
    40764080                ENDDO
     
    40904094             ENDDO
    40914095          ELSE
    4092              DO  i = nxlg, nxrg
    4093                 DO  j = nysg, nyng
     4096             DO  i = nxl, nxr
     4097                DO  j = nys, nyn
    40944098                   local_pf(i,j,nzb+1) = r_a_av(j,i)
    40954099                ENDDO
     
    41084112             ENDDO
    41094113          ELSE
    4110              DO  i = nxlg, nxrg
    4111                 DO  j = nysg, nyng
     4114             DO  i = nxl, nxr
     4115                DO  j = nys, nyn
    41124116                   local_pf(i,j,nzb+1) = r_s_av(j,i)
    41134117                ENDDO
     
    41284132             ENDDO
    41294133          ELSE
    4130              DO  i = nxlg, nxrg
    4131                 DO  j = nysg, nyng
     4134             DO  i = nxl, nxr
     4135                DO  j = nys, nyn
    41324136                   DO k = nzb_soil, nzt_soil
    41334137                      local_pf(i,j,k) = t_soil_av(k,j,i)
     
    41774181    LOGICAL      ::  found !<
    41784182
    4179     REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb_soil:nzt_soil) ::  local_pf !<
     4183    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_soil:nzt_soil) ::  local_pf !<
    41804184
    41814185
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r2302 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data any more
     29!
     30! 2302 2017-07-03 14:07:20Z suehring
    2731! Reading of 3D topography using NetCDF data type NC_BYTE
    2832!
     
    13071311!
    13081312!--       Define x-axis (for scalar position)
    1309           CALL netcdf_create_dim( id_set_3d(av), 'x', nx+2, id_dim_x_3d(av),   &
     1313          CALL netcdf_create_dim( id_set_3d(av), 'x', nx+1, id_dim_x_3d(av),   &
    13101314                                  73 )
    13111315          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av) /), 'x',   &
     
    13141318!
    13151319!--       Define x-axis (for u position)
    1316           CALL netcdf_create_dim( id_set_3d(av), 'xu', nx+2, id_dim_xu_3d(av), &
     1320          CALL netcdf_create_dim( id_set_3d(av), 'xu', nx+1, id_dim_xu_3d(av), &
    13171321                                  358 )
    13181322          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_xu_3d(av) /), 'xu', &
     
    13211325!
    13221326!--       Define y-axis (for scalar position)
    1323           CALL netcdf_create_dim( id_set_3d(av), 'y', ny+2, id_dim_y_3d(av),   &
     1327          CALL netcdf_create_dim( id_set_3d(av), 'y', ny+1, id_dim_y_3d(av),   &
    13241328                                  76 )
    13251329          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_y_3d(av) /), 'y',   &
     
    13281332!
    13291333!--       Define y-axis (for v position)
    1330           CALL netcdf_create_dim( id_set_3d(av), 'yv', ny+2, id_dim_yv_3d(av), &
     1334          CALL netcdf_create_dim( id_set_3d(av), 'yv', ny+1, id_dim_yv_3d(av), &
    13311335                                  361 )
    13321336          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_yv_3d(av) /), 'yv', &
     
    15371541!
    15381542!--          Write data for x (shifted by +dx/2) and xu axis
    1539              ALLOCATE( netcdf_data(0:nx+1) )
    1540 
    1541              DO  i = 0, nx+1
     1543             ALLOCATE( netcdf_data(0:nx) )
     1544
     1545             DO  i = 0, nx
    15421546                netcdf_data(i) = ( i + 0.5 ) * dx
    15431547             ENDDO
     
    15451549             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av),  &
    15461550                                     netcdf_data, start = (/ 1 /),    &
    1547                                      count = (/ nx+2 /) )
     1551                                     count = (/ nx+1 /) )
    15481552             CALL netcdf_handle_error( 'netcdf_define_header', 83 )
    15491553
    1550              DO  i = 0, nx+1
     1554             DO  i = 0, nx
    15511555                netcdf_data(i) = i * dx
    15521556             ENDDO
     
    15541558             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_xu_3d(av), &
    15551559                                     netcdf_data, start = (/ 1 /),    &
    1556                                      count = (/ nx+2 /) )
     1560                                     count = (/ nx+1 /) )
    15571561             CALL netcdf_handle_error( 'netcdf_define_header', 385 )
    15581562
     
    15611565!
    15621566!--          Write data for y (shifted by +dy/2) and yv axis
    1563              ALLOCATE( netcdf_data(0:ny+1) )
    1564 
    1565              DO  i = 0, ny+1
     1567             ALLOCATE( netcdf_data(0:ny) )
     1568
     1569             DO  i = 0, ny
    15661570                netcdf_data(i) = ( i + 0.5_wp ) * dy
    15671571             ENDDO
     
    15691573             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av),  &
    15701574                                     netcdf_data, start = (/ 1 /),    &
    1571                                      count = (/ ny+2 /) )
     1575                                     count = (/ ny+1 /) )
    15721576             CALL netcdf_handle_error( 'netcdf_define_header', 84 )
    15731577
    1574              DO  i = 0, ny+1
     1578             DO  i = 0, ny
    15751579                netcdf_data(i) = i * dy
    15761580             ENDDO
     
    15781582             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_yv_3d(av), &
    15791583                                     netcdf_data, start = (/ 1 /),    &
    1580                                      count = (/ ny+2 /))
     1584                                     count = (/ ny+1 /))
    15811585             CALL netcdf_handle_error( 'netcdf_define_header', 387 )
    15821586
     
    16121616               netcdf_data_format > 4 )  THEN
    16131617
    1614              IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    1615                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    1616                                         zu_s_inner(nxl:nxr+1,nys:nyn),         &
    1617                                         start = (/ nxl+1, nys+1 /),            &
    1618                                         count = (/ nxr-nxl+2, nyn-nys+1 /) )
    1619              ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    1620                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    1621                                         zu_s_inner(nxl:nxr,nys:nyn+1),         &
    1622                                         start = (/ nxl+1, nys+1 /),            &
    1623                                         count = (/ nxr-nxl+1, nyn-nys+2 /) )
    1624              ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    1625                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    1626                                         zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
    1627                                         start = (/ nxl+1, nys+1 /),            &
    1628                                         count = (/ nxr-nxl+2, nyn-nys+2 /) )
    1629              ELSE
     1618!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     1619!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1620!                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
     1621!                                        start = (/ nxl+1, nys+1 /),            &
     1622!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     1623!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     1624!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1625!                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
     1626!                                        start = (/ nxl+1, nys+1 /),            &
     1627!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     1628!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     1629!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1630!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
     1631!                                        start = (/ nxl+1, nys+1 /),            &
     1632!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     1633!             ELSE
    16301634                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    16311635                                        zu_s_inner(nxl:nxr,nys:nyn),           &
    16321636                                        start = (/ nxl+1, nys+1 /),            &
    16331637                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    1634              ENDIF
     1638!             ENDIF
    16351639             CALL netcdf_handle_error( 'netcdf_define_header', 419 )
    16361640
    1637              IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    1638                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    1639                                         zw_w_inner(nxl:nxr+1,nys:nyn),         &
    1640                                         start = (/ nxl+1, nys+1 /),            &
    1641                                         count = (/ nxr-nxl+2, nyn-nys+1 /) )
    1642              ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    1643                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    1644                                         zw_w_inner(nxl:nxr,nys:nyn+1),         &
    1645                                         start = (/ nxl+1, nys+1 /),            &
    1646                                         count = (/ nxr-nxl+1, nyn-nys+2 /) )
    1647              ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    1648                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    1649                                         zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
    1650                                         start = (/ nxl+1, nys+1 /),            &
    1651                                         count = (/ nxr-nxl+2, nyn-nys+2 /) )
    1652              ELSE
     1641!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     1642!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1643!                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
     1644!                                        start = (/ nxl+1, nys+1 /),            &
     1645!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     1646!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     1647!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1648!                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
     1649!                                        start = (/ nxl+1, nys+1 /),            &
     1650!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     1651!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     1652!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1653!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
     1654!                                        start = (/ nxl+1, nys+1 /),            &
     1655!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     1656!             ELSE
    16531657                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    16541658                                        zw_w_inner(nxl:nxr,nys:nyn),           &
    16551659                                        start = (/ nxl+1, nys+1 /),            &
    16561660                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    1657              ENDIF
     1661!             ENDIF
    16581662             CALL netcdf_handle_error( 'netcdf_define_header', 420 )
    16591663
     
    19611965!
    19621966!--       Define x-axis (for scalar position)
    1963           CALL netcdf_create_dim( id_set_xy(av), 'x', nx+2, id_dim_x_xy(av),   &
     1967          CALL netcdf_create_dim( id_set_xy(av), 'x', nx+1, id_dim_x_xy(av),   &
    19641968                                  113 )
    19651969          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av) /), 'x',   &
     
    19681972!
    19691973!--       Define x-axis (for u position)
    1970           CALL netcdf_create_dim( id_set_xy(av), 'xu', nx+2,                   &
     1974          CALL netcdf_create_dim( id_set_xy(av), 'xu', nx+1,                   &
    19711975                                  id_dim_xu_xy(av), 388 )
    19721976          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_xu_xy(av) /), 'xu', &
     
    19751979!
    19761980!--       Define y-axis (for scalar position)
    1977           CALL netcdf_create_dim( id_set_xy(av), 'y', ny+2, id_dim_y_xy(av),   &
     1981          CALL netcdf_create_dim( id_set_xy(av), 'y', ny+1, id_dim_y_xy(av),   &
    19781982                                  116 )
    19791983          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_y_xy(av) /), 'y',   &
     
    19821986!
    19831987!--       Define y-axis (for scalar position)
    1984           CALL netcdf_create_dim( id_set_xy(av), 'yv', ny+2,                   &
     1988          CALL netcdf_create_dim( id_set_xy(av), 'yv', ny+1,                   &
    19851989                                  id_dim_yv_xy(av), 364 )
    19861990          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_yv_xy(av) /), 'yv', &
     
    22552259!
    22562260!--          Write data for x (shifted by +dx/2) and xu axis
    2257              ALLOCATE( netcdf_data(0:nx+1) )
    2258 
    2259              DO  i = 0, nx+1
     2261             ALLOCATE( netcdf_data(0:nx) )
     2262
     2263             DO  i = 0, nx
    22602264                netcdf_data(i) = ( i + 0.5_wp ) * dx
    22612265             ENDDO
     
    22632267             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av), &
    22642268                                     netcdf_data, start = (/ 1 /),   &
    2265                                      count = (/ nx+2 /) )
     2269                                     count = (/ nx+1 /) )
    22662270             CALL netcdf_handle_error( 'netcdf_define_header', 127 )
    22672271
    2268              DO  i = 0, nx+1
     2272             DO  i = 0, nx
    22692273                netcdf_data(i) = i * dx
    22702274             ENDDO
     
    22722276             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_xu_xy(av), &
    22732277                                     netcdf_data, start = (/ 1 /),    &
    2274                                      count = (/ nx+2 /) )
     2278                                     count = (/ nx+1 /) )
    22752279             CALL netcdf_handle_error( 'netcdf_define_header', 367 )
    22762280
     
    22812285             ALLOCATE( netcdf_data(0:ny+1) )
    22822286
    2283              DO  i = 0, ny+1
     2287             DO  i = 0, ny
    22842288                netcdf_data(i) = ( i + 0.5_wp ) * dy
    22852289             ENDDO
     
    22872291             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av), &
    22882292                                     netcdf_data, start = (/ 1 /),   &
    2289                                      count = (/ ny+2 /))
     2293                                     count = (/ ny+1 /))
    22902294             CALL netcdf_handle_error( 'netcdf_define_header', 128 )
    22912295
    2292              DO  i = 0, ny+1
     2296             DO  i = 0, ny
    22932297                netcdf_data(i) = i * dy
    22942298             ENDDO
     
    22962300             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_yv_xy(av), &
    22972301                                     netcdf_data, start = (/ 1 /),    &
    2298                                      count = (/ ny+2 /))
     2302                                     count = (/ ny+1 /))
    22992303             CALL netcdf_handle_error( 'netcdf_define_header', 368 )
    23002304
     
    23092313               netcdf_data_format > 4  )  THEN
    23102314
    2311              IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    2312                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    2313                                         zu_s_inner(nxl:nxr+1,nys:nyn),         &
    2314                                         start = (/ nxl+1, nys+1 /),            &
    2315                                         count = (/ nxr-nxl+2, nyn-nys+1 /) )
    2316              ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    2317                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    2318                                         zu_s_inner(nxl:nxr,nys:nyn+1),         &
    2319                                         start = (/ nxl+1, nys+1 /),            &
    2320                                         count = (/ nxr-nxl+1, nyn-nys+2 /) )
    2321              ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    2322                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    2323                                         zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
    2324                                         start = (/ nxl+1, nys+1 /),            &
    2325                                         count = (/ nxr-nxl+2, nyn-nys+2 /) )
    2326              ELSE
     2315!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     2316!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2317!                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
     2318!                                        start = (/ nxl+1, nys+1 /),            &
     2319!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     2320!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     2321!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2322!                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
     2323!                                        start = (/ nxl+1, nys+1 /),            &
     2324!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     2325!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     2326!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2327!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
     2328!                                        start = (/ nxl+1, nys+1 /),            &
     2329!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     2330!             ELSE
    23272331                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    23282332                                        zu_s_inner(nxl:nxr,nys:nyn),           &
    23292333                                        start = (/ nxl+1, nys+1 /),            &
    23302334                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    2331              ENDIF
     2335!             ENDIF
    23322336             CALL netcdf_handle_error( 'netcdf_define_header', 427 )
    23332337
    2334              IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    2335                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    2336                                         zw_w_inner(nxl:nxr+1,nys:nyn),         &
    2337                                         start = (/ nxl+1, nys+1 /),            &
    2338                                         count = (/ nxr-nxl+2, nyn-nys+1 /) )
    2339              ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    2340                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    2341                                         zw_w_inner(nxl:nxr,nys:nyn+1),         &
    2342                                         start = (/ nxl+1, nys+1 /),            &
    2343                                         count = (/ nxr-nxl+1, nyn-nys+2 /) )
    2344              ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    2345                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    2346                                         zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
    2347                                         start = (/ nxl+1, nys+1 /),            &
    2348                                         count = (/ nxr-nxl+2, nyn-nys+2 /) )
    2349              ELSE
     2338!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     2339!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2340!                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
     2341!                                        start = (/ nxl+1, nys+1 /),            &
     2342!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     2343!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     2344!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2345!                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
     2346!                                        start = (/ nxl+1, nys+1 /),            &
     2347!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     2348!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     2349!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2350!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
     2351!                                        start = (/ nxl+1, nys+1 /),            &
     2352!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     2353!             ELSE
    23502354                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    23512355                                        zw_w_inner(nxl:nxr,nys:nyn),           &
    23522356                                        start = (/ nxl+1, nys+1 /),            &
    23532357                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    2354              ENDIF
     2358!             ENDIF
    23552359             CALL netcdf_handle_error( 'netcdf_define_header', 428 )
    23562360
     
    26842688!
    26852689!--       Define x-axis (for scalar position)
    2686           CALL netcdf_create_dim( id_set_xz(av), 'x', nx+2, id_dim_x_xz(av),   &
     2690          CALL netcdf_create_dim( id_set_xz(av), 'x', nx+1, id_dim_x_xz(av),   &
    26872691                                  150 )
    26882692          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_x_xz(av) /), 'x',   &
     
    26912695!
    26922696!--       Define x-axis (for u position)
    2693           CALL netcdf_create_dim( id_set_xz(av), 'xu', nx+2, id_dim_xu_xz(av), &
     2697          CALL netcdf_create_dim( id_set_xz(av), 'xu', nx+1, id_dim_xu_xz(av), &
    26942698                                  372 )
    26952699          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_xu_xz(av) /), 'xu', &
     
    29402944!
    29412945!--          Write data for x (shifted by +dx/2) and xu axis
    2942              ALLOCATE( netcdf_data(0:nx+1) )
    2943 
    2944              DO  i = 0, nx+1
     2946             ALLOCATE( netcdf_data(0:nx) )
     2947
     2948             DO  i = 0, nx
    29452949                netcdf_data(i) = ( i + 0.5_wp ) * dx
    29462950             ENDDO
     
    29482952             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av), &
    29492953                                     netcdf_data, start = (/ 1 /),   &
    2950                                      count = (/ nx+2 /) )
     2954                                     count = (/ nx+1 /) )
    29512955             CALL netcdf_handle_error( 'netcdf_define_header', 165 )
    29522956
    2953              DO  i = 0, nx+1
     2957             DO  i = 0, nx
    29542958                netcdf_data(i) = i * dx
    29552959             ENDDO
     
    29572961             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_xu_xz(av), &
    29582962                                     netcdf_data, start = (/ 1 /),    &
    2959                                      count = (/ nx+2 /) )
     2963                                     count = (/ nx+1 /) )
    29602964             CALL netcdf_handle_error( 'netcdf_define_header', 377 )
    29612965
     
    33373341!
    33383342!--       Define y-axis (for scalar position)
    3339           CALL netcdf_create_dim( id_set_yz(av), 'y', ny+2, id_dim_y_yz(av),   &
     3343          CALL netcdf_create_dim( id_set_yz(av), 'y', ny+1, id_dim_y_yz(av),   &
    33403344                                  189 )
    33413345          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_y_yz(av) /), 'y',   &
     
    33443348!
    33453349!--       Define y-axis (for v position)
    3346           CALL netcdf_create_dim( id_set_yz(av), 'yv', ny+2, id_dim_yv_yz(av), &
     3350          CALL netcdf_create_dim( id_set_yz(av), 'yv', ny+1, id_dim_yv_yz(av), &
    33473351                                  380 )
    33483352          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_yv_yz(av) /), 'yv', &
     
    35923596!
    35933597!--          Write data for y (shifted by +dy/2) and yv axis
    3594              ALLOCATE( netcdf_data(0:ny+1) )
    3595 
    3596              DO  j = 0, ny+1
     3598             ALLOCATE( netcdf_data(0:ny) )
     3599
     3600             DO  j = 0, ny
    35973601                netcdf_data(j) = ( j + 0.5_wp ) * dy
    35983602             ENDDO
     
    36003604             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av), &
    36013605                                     netcdf_data, start = (/ 1 /),   &
    3602                                      count = (/ ny+2 /) )
     3606                                     count = (/ ny+1 /) )
    36033607             CALL netcdf_handle_error( 'netcdf_define_header', 204 )
    36043608
    3605              DO  j = 0, ny+1
     3609             DO  j = 0, ny
    36063610                netcdf_data(j) = j * dy
    36073611             ENDDO
     
    36093613             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_yv_yz(av), &
    36103614                                     netcdf_data, start = (/ 1 /),    &
    3611                                      count = (/ ny+2 /) )
     3615                                     count = (/ ny+1 /) )
    36123616             CALL netcdf_handle_error( 'netcdf_define_header', 384 )
    36133617
  • palm/trunk/SOURCE/palm.f90

    r2320 r2512  
    2525! -----------------
    2626! $Id$
     27! user interface required revision updated
     28!
     29! 2320 2017-07-21 12:47:43Z suehring
    2730! Modularize large-scale forcing and nudging
    2831!
     
    237240
    238241    version = 'PALM 4.0'
    239     user_interface_required_revision = 'r2297'
     242    user_interface_required_revision = 'r2512'
    240243
    241244#if defined( __parallel )
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2318 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29!
     30! 2318 2017-07-20 17:27:44Z suehring
    2731! Get topography top index via Function call
    2832!
     
    356360    LOGICAL      ::  found !<
    357361
    358     REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nz_do3d) ::  local_pf !<
     362    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nz_do3d) ::  local_pf !<
    359363
    360364
     
    365369
    366370      CASE ( 'pcm_heatrate' )
    367          CALL exchange_horiz( pc_heating_rate, nbgp )
    368371         IF ( av == 0 )  THEN
    369             DO  i = nxlg, nxrg
    370                DO  j = nysg, nyng
     372            DO  i = nxl, nxr
     373               DO  j = nys, nyn
    371374                  DO  k = nzb_s_inner(j,i), nz_do3d
    372375                     local_pf(i,j,k) = pc_heating_rate(k-nzb_s_inner(j,i),j,i)
     
    379382      CASE ( 'pcm_lad' )
    380383         IF ( av == 0 )  THEN
    381             DO  i = nxlg, nxrg
    382                DO  j = nysg, nyng
     384            DO  i = nxl, nxr
     385               DO  j = nys, nyn
    383386                  DO  k = nzb_s_inner(j,i), nz_do3d
    384387                     local_pf(i,j,k) = lad_s(k-nzb_s_inner(j,i),j,i)
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r2504 r2512  
    2525! -----------------
    2626! $Id$
     27! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
     28! no output of ghost layer data
     29!
     30! 2504 2017-09-27 10:36:13Z maronga
    2731! Updates pavement types and albedo parameters
    2832!
     
    28102814    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    28112815
    2812     REAL(wp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nzt+1) ::  local_pf !<
     2816    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
    28132817
    28142818    found = .TRUE.
     
    28182822       CASE ( 'rad_net*_xy' )        ! 2d-array
    28192823          IF ( av == 0 ) THEN
    2820              DO  i = nxlg, nxrg
    2821                 DO  j = nysg, nyng
     2824             DO  i = nxl, nxr
     2825                DO  j = nys, nyn
    28222826                   local_pf(i,j,nzb+1) = rad_net(j,i)
    28232827                ENDDO
    28242828             ENDDO
    28252829          ELSE
    2826              DO  i = nxlg, nxrg
    2827                 DO  j = nysg, nyng
     2830             DO  i = nxl, nxr
     2831                DO  j = nys, nyn
    28282832                   local_pf(i,j,nzb+1) = rad_net_av(j,i)
    28292833                ENDDO
     
    28362840       CASE ( 'rad_lw_in_xy', 'rad_lw_in_xz', 'rad_lw_in_yz' )
    28372841          IF ( av == 0 ) THEN
    2838              DO  i = nxlg, nxrg
    2839                 DO  j = nysg, nyng
     2842             DO  i = nxl, nxr
     2843                DO  j = nys, nyn
    28402844                   DO  k = nzb, nzt+1
    28412845                      local_pf(i,j,k) = rad_lw_in(k,j,i)
     
    28442848             ENDDO
    28452849          ELSE
    2846              DO  i = nxlg, nxrg
    2847                 DO  j = nysg, nyng
     2850             DO  i = nxl, nxr
     2851                DO  j = nys, nyn
    28482852                   DO  k = nzb, nzt+1
    28492853                      local_pf(i,j,k) = rad_lw_in_av(k,j,i)
     
    28562860       CASE ( 'rad_lw_out_xy', 'rad_lw_out_xz', 'rad_lw_out_yz' )
    28572861          IF ( av == 0 ) THEN
    2858              DO  i = nxlg, nxrg
    2859                 DO  j = nysg, nyng
     2862             DO  i = nxl, nxr
     2863                DO  j = nys, nyn
    28602864                   DO  k = nzb, nzt+1
    28612865                      local_pf(i,j,k) = rad_lw_out(k,j,i)
     
    28642868             ENDDO
    28652869          ELSE
    2866              DO  i = nxlg, nxrg
    2867                 DO  j = nysg, nyng
     2870             DO  i = nxl, nxr
     2871                DO  j = nys, nyn
    28682872                   DO  k = nzb, nzt+1
    28692873                      local_pf(i,j,k) = rad_lw_out_av(k,j,i)
     
    28762880       CASE ( 'rad_lw_cs_hr_xy', 'rad_lw_cs_hr_xz', 'rad_lw_cs_hr_yz' )
    28772881          IF ( av == 0 ) THEN
    2878              DO  i = nxlg, nxrg
    2879                 DO  j = nysg, nyng
     2882             DO  i = nxl, nxr
     2883                DO  j = nys, nyn
    28802884                   DO  k = nzb, nzt+1
    28812885                      local_pf(i,j,k) = rad_lw_cs_hr(k,j,i)
     
    28842888             ENDDO
    28852889          ELSE
    2886              DO  i = nxlg, nxrg
    2887                 DO  j = nysg, nyng
     2890             DO  i = nxl, nxr
     2891                DO  j = nys, nyn
    28882892                   DO  k = nzb, nzt+1
    28892893                      local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i)
     
    28962900       CASE ( 'rad_lw_hr_xy', 'rad_lw_hr_xz', 'rad_lw_hr_yz' )
    28972901          IF ( av == 0 ) THEN
    2898              DO  i = nxlg, nxrg
    2899                 DO  j = nysg, nyng
     2902             DO  i = nxl, nxr
     2903                DO  j = nys, nyn
    29002904                   DO  k = nzb, nzt+1
    29012905                      local_pf(i,j,k) = rad_lw_hr(k,j,i)
     
    29042908             ENDDO
    29052909          ELSE
    2906              DO  i = nxlg, nxrg
    2907                 DO  j = nysg, nyng
     2910             DO  i = nxl, nxr
     2911                DO  j = nys, nyn
    29082912                   DO  k = nzb, nzt+1
    29092913                      local_pf(i,j,k) = rad_lw_hr_av(k,j,i)
     
    29162920       CASE ( 'rad_sw_in_xy', 'rad_sw_in_xz', 'rad_sw_in_yz' )
    29172921          IF ( av == 0 ) THEN
    2918              DO  i = nxlg, nxrg
    2919                 DO  j = nysg, nyng
     2922             DO  i = nxl, nxr
     2923                DO  j = nys, nyn
    29202924                   DO  k = nzb, nzt+1
    29212925                      local_pf(i,j,k) = rad_sw_in(k,j,i)
     
    29242928             ENDDO
    29252929          ELSE
    2926              DO  i = nxlg, nxrg
    2927                 DO  j = nysg, nyng
     2930             DO  i = nxl, nxr
     2931                DO  j = nys, nyn
    29282932                   DO  k = nzb, nzt+1
    29292933                      local_pf(i,j,k) = rad_sw_in_av(k,j,i)
     
    29362940       CASE ( 'rad_sw_out_xy', 'rad_sw_out_xz', 'rad_sw_out_yz' )
    29372941          IF ( av == 0 ) THEN
    2938              DO  i = nxlg, nxrg
    2939                 DO  j = nysg, nyng
     2942             DO  i = nxl, nxr
     2943                DO  j = nys, nyn
    29402944                   DO  k = nzb, nzt+1
    29412945                      local_pf(i,j,k) = rad_sw_out(k,j,i)
     
    29442948             ENDDO
    29452949          ELSE
    2946              DO  i = nxlg, nxrg
    2947                 DO  j = nysg, nyng
     2950             DO  i = nxl, nxr
     2951                DO  j = nys, nyn
    29482952                   DO  k = nzb, nzt+1
    29492953                      local_pf(i,j,k) = rad_sw_out_av(k,j,i)
     
    29562960       CASE ( 'rad_sw_cs_hr_xy', 'rad_sw_cs_hr_xz', 'rad_sw_cs_hr_yz' )
    29572961          IF ( av == 0 ) THEN
    2958              DO  i = nxlg, nxrg
    2959                 DO  j = nysg, nyng
     2962             DO  i = nxl, nxr
     2963                DO  j = nys, nyn
    29602964                   DO  k = nzb, nzt+1
    29612965                      local_pf(i,j,k) = rad_sw_cs_hr(k,j,i)
     
    29642968             ENDDO
    29652969          ELSE
    2966              DO  i = nxlg, nxrg
    2967                 DO  j = nysg, nyng
     2970             DO  i = nxl, nxr
     2971                DO  j = nys, nyn
    29682972                   DO  k = nzb, nzt+1
    29692973                      local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i)
     
    29762980       CASE ( 'rad_sw_hr_xy', 'rad_sw_hr_xz', 'rad_sw_hr_yz' )
    29772981          IF ( av == 0 ) THEN
    2978              DO  i = nxlg, nxrg
    2979                 DO  j = nysg, nyng
     2982             DO  i = nxl, nxr
     2983                DO  j = nys, nyn
    29802984                   DO  k = nzb, nzt+1
    29812985                      local_pf(i,j,k) = rad_sw_hr(k,j,i)
     
    29842988             ENDDO
    29852989          ELSE
    2986              DO  i = nxlg, nxrg
    2987                 DO  j = nysg, nyng
     2990             DO  i = nxl, nxr
     2991                DO  j = nys, nyn
    29882992                   DO  k = nzb, nzt+1
    29892993                      local_pf(i,j,k) = rad_sw_hr_av(k,j,i)
     
    30283032    LOGICAL      ::  found !<
    30293033
    3030     REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nzt+1) ::  local_pf !<
     3034    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
    30313035
    30323036
     
    30383042      CASE ( 'rad_sw_in' )
    30393043         IF ( av == 0 )  THEN
    3040             DO  i = nxlg, nxrg
    3041                DO  j = nysg, nyng
     3044            DO  i = nxl, nxr
     3045               DO  j = nys, nyn
    30423046                  DO  k = nzb, nzt+1
    30433047                     local_pf(i,j,k) = rad_sw_in(k,j,i)
     
    30463050            ENDDO
    30473051         ELSE
    3048             DO  i = nxlg, nxrg
    3049                DO  j = nysg, nyng
     3052            DO  i = nxl, nxr
     3053               DO  j = nys, nyn
    30503054                  DO  k = nzb, nzt+1
    30513055                     local_pf(i,j,k) = rad_sw_in_av(k,j,i)
     
    30573061      CASE ( 'rad_sw_out' )
    30583062         IF ( av == 0 )  THEN
    3059             DO  i = nxlg, nxrg
    3060                DO  j = nysg, nyng
     3063            DO  i = nxl, nxr
     3064               DO  j = nys, nyn
    30613065                  DO  k = nzb, nzt+1
    30623066                     local_pf(i,j,k) = rad_sw_out(k,j,i)
     
    30653069            ENDDO
    30663070         ELSE
    3067             DO  i = nxlg, nxrg
    3068                DO  j = nysg, nyng
     3071            DO  i = nxl, nxr
     3072               DO  j = nys, nyn
    30693073                  DO  k = nzb, nzt+1
    30703074                     local_pf(i,j,k) = rad_sw_out_av(k,j,i)
     
    30763080      CASE ( 'rad_sw_cs_hr' )
    30773081         IF ( av == 0 )  THEN
    3078             DO  i = nxlg, nxrg
    3079                DO  j = nysg, nyng
     3082            DO  i = nxl, nxr
     3083               DO  j = nys, nyn
    30803084                  DO  k = nzb, nzt+1
    30813085                     local_pf(i,j,k) = rad_sw_cs_hr(k,j,i)
     
    30843088            ENDDO
    30853089         ELSE
    3086             DO  i = nxlg, nxrg
    3087                DO  j = nysg, nyng
     3090            DO  i = nxl, nxr
     3091               DO  j = nys, nyn
    30883092                  DO  k = nzb, nzt+1
    30893093                     local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i)
     
    30953099      CASE ( 'rad_sw_hr' )
    30963100         IF ( av == 0 )  THEN
    3097             DO  i = nxlg, nxrg
    3098                DO  j = nysg, nyng
     3101            DO  i = nxl, nxr
     3102               DO  j = nys, nyn
    30993103                  DO  k = nzb, nzt+1
    31003104                     local_pf(i,j,k) = rad_sw_hr(k,j,i)
     
    31033107            ENDDO
    31043108         ELSE
    3105             DO  i = nxlg, nxrg
    3106                DO  j = nysg, nyng
     3109            DO  i = nxl, nxr
     3110               DO  j = nys, nyn
    31073111                  DO  k = nzb, nzt+1
    31083112                     local_pf(i,j,k) = rad_sw_hr_av(k,j,i)
     
    31143118      CASE ( 'rad_lw_in' )
    31153119         IF ( av == 0 )  THEN
    3116             DO  i = nxlg, nxrg
    3117                DO  j = nysg, nyng
     3120            DO  i = nxl, nxr
     3121               DO  j = nys, nyn
    31183122                  DO  k = nzb, nzt+1
    31193123                     local_pf(i,j,k) = rad_lw_in(k,j,i)
     
    31223126            ENDDO
    31233127         ELSE
    3124             DO  i = nxlg, nxrg
    3125                DO  j = nysg, nyng
     3128            DO  i = nxl, nxr
     3129               DO  j = nys, nyn
    31263130                  DO  k = nzb, nzt+1
    31273131                     local_pf(i,j,k) = rad_lw_in_av(k,j,i)
     
    31333137      CASE ( 'rad_lw_out' )
    31343138         IF ( av == 0 )  THEN
    3135             DO  i = nxlg, nxrg
    3136                DO  j = nysg, nyng
     3139            DO  i = nxl, nxr
     3140               DO  j = nys, nyn
    31373141                  DO  k = nzb, nzt+1
    31383142                     local_pf(i,j,k) = rad_lw_out(k,j,i)
     
    31413145            ENDDO
    31423146         ELSE
    3143             DO  i = nxlg, nxrg
    3144                DO  j = nysg, nyng
     3147            DO  i = nxl, nxr
     3148               DO  j = nys, nyn
    31453149                  DO  k = nzb, nzt+1
    31463150                     local_pf(i,j,k) = rad_lw_out_av(k,j,i)
     
    31523156      CASE ( 'rad_lw_cs_hr' )
    31533157         IF ( av == 0 )  THEN
    3154             DO  i = nxlg, nxrg
    3155                DO  j = nysg, nyng
     3158            DO  i = nxl, nxr
     3159               DO  j = nys, nyn
    31563160                  DO  k = nzb, nzt+1
    31573161                     local_pf(i,j,k) = rad_lw_cs_hr(k,j,i)
     
    31603164            ENDDO
    31613165         ELSE
    3162             DO  i = nxlg, nxrg
    3163                DO  j = nysg, nyng
     3166            DO  i = nxl, nxr
     3167               DO  j = nys, nyn
    31643168                  DO  k = nzb, nzt+1
    31653169                     local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i)
     
    31713175      CASE ( 'rad_lw_hr' )
    31723176         IF ( av == 0 )  THEN
    3173             DO  i = nxlg, nxrg
    3174                DO  j = nysg, nyng
     3177            DO  i = nxl, nxr
     3178               DO  j = nys, nyn
    31753179                  DO  k = nzb, nzt+1
    31763180                     local_pf(i,j,k) = rad_lw_hr(k,j,i)
     
    31793183            ENDDO
    31803184         ELSE
    3181             DO  i = nxlg, nxrg
    3182                DO  j = nysg, nyng
     3185            DO  i = nxl, nxr
     3186               DO  j = nys, nyn
    31833187                  DO  k = nzb, nzt+1
    31843188                     local_pf(i,j,k) = rad_lw_hr_av(k,j,i)
  • 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
  • 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 
  • 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)
  • palm/trunk/SOURCE/user_parin.f90

    r2298 r2512  
    2525! -----------------
    2626! $Id$
     27! current interface revision number number set to r2512
     28!
     29! 2298 2017-06-29 09:28:18Z raasch
    2730! user interface current revision updated
    2831!
     
    102105!-- current revision does not match with previous revisions (e.g. if routines
    103106!-- have been added/deleted or if parameter lists in subroutines have been changed).
    104     user_interface_current_revision = 'r2297'
     107    user_interface_current_revision = 'r2512'
    105108
    106109!
  • palm/trunk/UTIL/combine_plot_fields.f90

    r2365 r2512  
    2525! -----------------
    2626! $Id$
     27! PALM output does not contain ghost layer data any more
     28! avs- and iso2d-related parts removed, handling of compressed data removed
     29!
     30! 2365 2017-08-21 14:59:59Z kanani
    2731! Vertical grid nesting implemented (SadiqHuq)
    2832!
     
    121125    INTEGER(iwp), DIMENSION(0:1,1000) ::  id_var, levels
    122126
    123     LOGICAL  ::  avs_output, compressed, found, iso2d_output, netcdf_output,   &
    124                  netcdf_parallel, netcdf_0, netcdf_1
     127    LOGICAL  ::  found, netcdf_output, netcdf_parallel, netcdf_0, netcdf_1
    125128    LOGICAL  ::  vnest
    126129
    127130    REAL(wp) ::  cpu_start_time, cpu_end_time, dx, simulated_time
    128     REAL(wp),  DIMENSION(:),   ALLOCATABLE   ::  eta, ho, hu
    129131    REAL(wp),  DIMENSION(:,:), ALLOCATABLE   ::  pf, pf_tmp
    130132    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE ::  pf3d, pf3d_tmp
     
    227229
    228230!
    229 !--       Inquire whether an iso2d parameter file exists
    230           INQUIRE( FILE='PLOT2D_'//modus//'_GLOBAL'//TRIM( model_string ), &
    231                EXIST=iso2d_output )
    232 
    233 !
    234231!--       Inquire whether a NetCDF file exists
    235232          INQUIRE( FILE='DATA_2D_'//modus//'_NETCDF'//TRIM( model_string ), &
     
    387384!--                File from PE0 contains special information at the beginning,
    388385!--                concerning the lower and upper indices of the total-domain
    389 !--                used in PALM (nxag, nxeg, nyag, nyeg) and the lower and
    390 !--                upper indices of the array to be written by this routine
    391 !--                (nxa, nxe, nya, nye). Usually in the horizontal directions
    392 !--                nxag=-1 and nxa=0 while all other variables have the same
    393 !--                value (i.e. nxeg=nxe).
     386!--                used in PALM (nxa, nxe, nya, nye).
    394387!--                Allocate necessary arrays, open the output file and write
    395388!--                the coordinate informations needed by ISO2D.
    396389                   IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 ) THEN
    397                       READ ( id+110 )  nxag, nxeg, nyag, nyeg
     390
    398391                      READ ( id+110 )  nxa, nxe, nya, nye
    399                       ALLOCATE ( eta(nya:nye), ho(nxa:nxe), hu(nxa:nxe), &
    400                                  pf(nxag:nxeg,nyag:nyeg) )
    401                       READ ( id+110 )  dx, eta, hu, ho
    402 
    403 
     392                      ALLOCATE ( pf(nxa:nxe,nya:nye) )
    404393!
    405394!--                   Set actual domain bounds to total domain
     
    407396                      ye_do = nye
    408397
    409                       IF ( iso2d_output )  THEN
    410                          OPEN ( 2, FILE='PLOT2D_'//modus//TRIM( model_string ),&
    411                                    FORM='UNFORMATTED' )
    412                          WRITE ( 2 )  dx, eta, hu, ho
    413                       ENDIF
    414398                   ENDIF
    415399!
    416400!--                Read output time
    417401                   IF ( netcdf_output  .AND.  id == 0 )  THEN
    418                       IF ( netcdf_1 )  THEN
    419                          READ ( id+110, END=998 )  simulated_time, time_step, av
    420                       ELSE
    421 !
    422 !--                      For compatibility with earlier PALM versions
    423                          READ ( id+110, END=998 )  simulated_time, time_step
    424                          av = 0
    425                       ENDIF
     402                      READ ( id+110, END=998 )  simulated_time, time_step, av
    426403                   ENDIF
    427404!
     
    460437                ENDDO
    461438!
    462 !--             Write the data of the total domain cross-section
    463                 IF ( iso2d_output )  WRITE ( 2 )  pf(nxa:nxe,nya:nye)
    464        
    465 !
    466 !--             Write same data in NetCDF format
     439!--             Write data in NetCDF format
    467440                IF ( netcdf_output )  THEN
    468441#if defined( __netcdf )
     
    544517             ENDDO
    545518             CLOSE ( 2 )
    546              DEALLOCATE ( eta, ho, hu, pf )
     519             DEALLOCATE ( pf )
    547520
    548521!
     
    598571       CALL SYSTEM_CLOCK( count, count_rate )
    599572       cpu_start_time = REAL( count ) / REAL( count_rate )
    600 
    601 !
    602 !--    Inquire whether an avs fld file exists
    603        INQUIRE( FILE='PLOT3D_FLD'//TRIM( model_string ), EXIST=avs_output )
    604573
    605574!
     
    639608
    640609!
    641 !--    Combination only works, if data are not compressed. In that case,
    642 !--    PALM created a flag file (PLOT3D_COMPRESSED)
    643        INQUIRE ( FILE='PLOT3D_COMPRESSED'//TRIM( model_string ), &
    644             EXIST=compressed )
    645 
    646 !
    647610!--    Find out the number of files and open them
    648        DO  WHILE ( found  .AND.  .NOT. compressed )
     611       DO  WHILE ( found )
    649612
    650613          OPEN ( danz+110, &
     
    678641             PRINT*, '    3D-data:     ', danz, ' file(s) found'
    679642          ELSE
    680              IF ( found .AND. compressed )  THEN
    681                 PRINT*, '+++ no 3D-data processing, since data are compressed'
    682              ELSE
    683                 PRINT*, '    no 3D-data file available'
    684              ENDIF
     643             PRINT*, '    no 3D-data file available'
    685644          ENDIF
    686645       ENDIF
     
    764723             DO  id = 0, danz-1
    765724!
    766 !--             File from PE0 contains special information at the beginning,
    767 !--             concerning the lower and upper indices of the total-domain used
    768 !--             in PALM (nxag, nxeg, nyag, nyeg) and the lower and
    769 !--             upper indices of the array to be written by this routine (nxa,
    770 !--             nxe, nya, nye, nza, nze). Usually nxag=-1 and nxa=0, nyag=-1
    771 !--             and nya=0, nzeg=nz and nze=nz_do3d.
    772 !--             Allocate necessary array and open the output file.
     725!--             File from PE0 contains at the beginning the index bounds
     726!--             of PALM's total domain.
     727!--             Allocate the array for storing the total domain data
    773728                IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 )  THEN
    774                    READ ( id+110 )  nxag, nxeg, nyag, nyeg
     729!                   READ ( id+110 )  nxag, nxeg, nyag, nyeg
    775730                   READ ( id+110 )  nxa, nxe, nya, nye, nza, nze
    776731                   ALLOCATE ( pf3d(nxa:nxe,nya:nye,nza:nze) )
    777                    IF ( avs_output )  THEN
    778                       OPEN ( 2, FILE='PLOT3D_DATA'//TRIM( model_string ), &
    779                              FORM='UNFORMATTED' )
    780                    ENDIF
    781732                ENDIF
    782733
     
    818769
    819770!
    820 !--          Write data of the total domain
    821              IF ( avs_output )  WRITE ( 2 )  pf3d(nxa:nxe,nya:nye,nza:nze)
    822        
    823 !
    824 !--          Write same data in NetCDF format
     771!--          Write data of the total domain in NetCDF format
    825772             IF ( netcdf_output )  THEN
    826773#if defined( __netcdf )
Note: See TracChangeset for help on using the changeset viewer.