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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/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
Note: See TracChangeset for help on using the changeset viewer.