Ignore:
Timestamp:
Mar 2, 2021 4:39:14 PM (3 years ago)
Author:
raasch
Message:

revised output of surface data via MPI-IO for better performance

File:
1 edited

Legend:

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

    r4872 r4893  
    2727! -----------------
    2828! $Id$
     29! revised output of surface data via MPI-IO for better performance
     30!
     31! 4872 2021-02-12 15:49:02Z raasch
    2932! internal switch removed from namelist
    3033!
     
    66086611 SUBROUTINE usm_rrd_local_mpi
    66096612
    6610 
    66116613    CHARACTER(LEN=1) ::  dum  !< dummy string to create input-variable name
    66126614
    66136615    INTEGER(iwp) ::  l  !< loop index for surface types
    66146616
    6615     INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start
    6616 
    6617     LOGICAL ::  ldum  !< dummy variable
     6617    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_end_index
     6618    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index
     6619
     6620    LOGICAL ::  data_to_read  !< dummy variable
     6621
    66186622
    66196623    DO  l = 0, 1
     
    66216625       WRITE( dum, '(I1)' )  l
    66226626
    6623        CALL rrd_mpi_io( 'usm_start_index_h_' //dum,  surf_usm_h(l)%start_index )
    6624        CALL rrd_mpi_io( 'usm_end_index_h_' //dum, surf_usm_h(l)%end_index )
    6625        CALL rrd_mpi_io( 'usm_global_start_h_' //dum, global_start )
    6626 
    6627        CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index, ldum, &
    6628                                          global_start )
    6629 
    6630        IF ( MAXVAL( surf_usm_h(l)%end_index ) <= 0 )  CYCLE
    6631 
    6632        IF ( .NOT.  ALLOCATED( t_surf_wall_h_1(l)%val ) )                                             &
     6627       CALL rrd_mpi_io( 'usm_global_start_h_' //dum, global_start_index )
     6628       CALL rrd_mpi_io( 'usm_global_end_h_' //dum, global_end_index )
     6629
     6630       CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,       &
     6631                                         data_to_read, global_start_index, global_end_index )
     6632       IF ( .NOT. data_to_read )  CYCLE
     6633
     6634       IF ( .NOT. ALLOCATED( t_surf_wall_h_1(l)%val ) )                                            &
    66336635          ALLOCATE( t_surf_wall_h_1(l)%val(1:surf_usm_h(l)%ns) )
    66346636       CALL rrd_mpi_io_surface( 't_surf_wall_h(' // dum // ')', t_surf_wall_h_1(l)%val )
    66356637
    6636        IF ( .NOT.  ALLOCATED( t_surf_window_h_1(l)%val ) )                                           &
     6638       IF ( .NOT. ALLOCATED( t_surf_window_h_1(l)%val ) )                                          &
    66376639          ALLOCATE( t_surf_window_h_1(l)%val(1:surf_usm_h(l)%ns) )
    66386640       CALL rrd_mpi_io_surface( 't_surf_window_h(' // dum // ')', t_surf_window_h_1(l)%val )
    66396641
    6640        IF ( .NOT.  ALLOCATED( t_surf_green_h_1(l)%val ) )                                            &
     6642       IF ( .NOT. ALLOCATED( t_surf_green_h_1(l)%val ) )                                           &
    66416643          ALLOCATE( t_surf_green_h_1(l)%val(1:surf_usm_h(l)%ns) )
    66426644       CALL rrd_mpi_io_surface( 't_surf_green_h(' // dum // ')', t_surf_green_h_1(l)%val )
    66436645
    6644        IF ( .NOT.  ALLOCATED( m_liq_usm_h_1(l)%val ) )                                             &
     6646       IF ( .NOT. ALLOCATED( m_liq_usm_h_1(l)%val ) )                                              &
    66456647          ALLOCATE( m_liq_usm_h_1(l)%val(1:surf_usm_h(l)%ns) )
    66466648       CALL rrd_mpi_io_surface( 'm_liq_usm_h(' // dum // ')', m_liq_usm_h_1(l)%val )
    66476649
    66486650       IF ( indoor_model )  THEN
    6649           IF ( .NOT.  ALLOCATED( surf_usm_h(l)%waste_heat ) )                                      &
     6651          IF ( .NOT. ALLOCATED( surf_usm_h(l)%waste_heat ) )                                       &
    66506652             ALLOCATE( surf_usm_h(l)%waste_heat(1:surf_usm_h(l)%ns) )
    66516653          CALL rrd_mpi_io_surface( 'waste_heat_h(' // dum // ')', surf_usm_h(l)%waste_heat )
    6652           IF ( .NOT.  ALLOCATED( surf_usm_h(l)%t_prev ) )                                          &
     6654          IF ( .NOT. ALLOCATED( surf_usm_h(l)%t_prev ) )                                           &
    66536655             ALLOCATE( surf_usm_h(l)%t_prev(1:surf_usm_h(l)%ns) )
    66546656          CALL rrd_mpi_io_surface( 't_prev_h(' // dum // ')', surf_usm_h(l)%t_prev )
     
    66606662       WRITE( dum, '(I1)' )  l
    66616663
    6662        CALL rrd_mpi_io( 'usm_start_index_v_' //dum, surf_usm_v(l)%start_index )
    6663        CALL rrd_mpi_io( 'usm_end_index_v_' // dum, surf_usm_v(l)%end_index )
    6664        CALL rrd_mpi_io( 'usm_global_start_v_' // dum, global_start )
    6665 
    6666        CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, ldum, &
    6667                                          global_start )
    6668 
    6669        IF ( MAXVAL( surf_usm_v(l)%end_index ) <= 0 )  CYCLE
    6670 
    6671        IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(l)%val ) )                                             &
     6664       CALL rrd_mpi_io( 'usm_global_start_v_' // dum, global_start_index )
     6665       CALL rrd_mpi_io( 'usm_global_end_v_' // dum, global_end_index )
     6666
     6667       CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index,       &
     6668                                         data_to_read, global_start_index, global_end_index )
     6669       IF ( .NOT. data_to_read )  CYCLE
     6670
     6671       IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%val ) )                                            &
    66726672          ALLOCATE( t_surf_wall_v_1(l)%val(1:surf_usm_v(l)%ns) )
    66736673       CALL rrd_mpi_io_surface( 't_surf_wall_v(' // dum // ')', t_surf_wall_v_1(l)%val )
    66746674
    6675        IF ( .NOT.  ALLOCATED( t_surf_window_v_1(l)%val ) )                                           &
     6675       IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%val ) )                                          &
    66766676          ALLOCATE( t_surf_window_v_1(l)%val(1:surf_usm_v(l)%ns) )
    66776677       CALL rrd_mpi_io_surface( 't_surf_window_v(' // dum // ')', t_surf_window_v_1(l)%val )
    66786678
    6679        IF ( .NOT.  ALLOCATED( t_surf_green_v_1(l)%val ) )                                            &
     6679       IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%val ) )                                           &
    66806680          ALLOCATE( t_surf_green_v_1(l)%val(1:surf_usm_v(l)%ns) )
    66816681       CALL rrd_mpi_io_surface( 't_surf_green_v(' // dum // ')', t_surf_green_v_1(l)%val)
    66826682
    66836683       IF ( indoor_model )  THEN
    6684           IF ( .NOT.  ALLOCATED( surf_usm_v(l)%waste_heat ) )                                      &
     6684          IF ( .NOT. ALLOCATED( surf_usm_v(l)%waste_heat ) )                                       &
    66856685             ALLOCATE( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
    66866686          CALL rrd_mpi_io_surface( 'waste_heat_v(' // dum // ')', surf_usm_v(l)%waste_heat )
    6687           IF ( .NOT.  ALLOCATED( surf_usm_v(l)%t_prev ) )                                          &
     6687          IF ( .NOT. ALLOCATED( surf_usm_v(l)%t_prev ) )                                           &
    66886688             ALLOCATE( surf_usm_v(l)%t_prev(1:surf_usm_v(l)%ns) )
    66896689          CALL rrd_mpi_io_surface( 't_prev_v(' // dum // ')', surf_usm_v(l)%t_prev )
     
    66966696       WRITE( dum, '(I1)' )  l
    66976697
    6698        CALL rrd_mpi_io( 'usm_start_index_h_2_' //dum,  surf_usm_h(l)%start_index )
    6699        CALL rrd_mpi_io( 'usm_end_index_h_2_' //dum, surf_usm_h(l)%end_index )
    6700        CALL rrd_mpi_io( 'usm_global_start_h_2_' //dum, global_start )
    6701 
    6702        CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index, ldum,          &
    6703                                          global_start )
    6704 
    6705        IF ( MAXVAL( surf_usm_h(l)%end_index ) <= 0 )  CYCLE
    6706 
    6707        IF ( .NOT.  ALLOCATED( t_wall_h_1(l)%val ) )                                                          &
     6698       CALL rrd_mpi_io( 'usm_global_start_h_2_' //dum, global_start_index )
     6699       CALL rrd_mpi_io( 'usm_global_end_h_2_' //dum, global_end_index )
     6700
     6701       CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,       &
     6702                                         data_to_read, global_start_index, global_end_index )
     6703       IF ( .NOT. data_to_read )  CYCLE
     6704
     6705       IF ( .NOT. ALLOCATED( t_wall_h_1(l)%val ) )                                                 &
    67086706          ALLOCATE( t_wall_h_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_h(l)%ns) )
    67096707       CALL rrd_mpi_io_surface( 't_wall_h(' // dum // ')', t_wall_h_1(l)%val )
    67106708
    6711        IF ( .NOT.  ALLOCATED( t_window_h_1(l)%val ) )                                                        &
     6709       IF ( .NOT. ALLOCATED( t_window_h_1(l)%val ) )                                               &
    67126710          ALLOCATE( t_window_h_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_h(l)%ns) )
    67136711       CALL rrd_mpi_io_surface( 't_window_h(' // dum // ')', t_window_h_1(l)%val )
    67146712
    6715        IF ( .NOT.  ALLOCATED( t_green_h_1(l)%val ) )                                                         &
     6713       IF ( .NOT. ALLOCATED( t_green_h_1(l)%val ) )                                                &
    67166714          ALLOCATE( t_green_h_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_h(l)%ns) )
    67176715       CALL rrd_mpi_io_surface( 't_green_h(' // dum // ')', t_green_h_1(l)%val )
     
    67236721       WRITE( dum, '(I1)' )  l
    67246722
    6725        CALL rrd_mpi_io( 'usm_start_index_v_2_' //dum, surf_usm_v(l)%start_index )
    6726        CALL rrd_mpi_io( 'usm_end_index_v_2_' // dum, surf_usm_v(l)%end_index )
    6727        CALL rrd_mpi_io( 'usm_global_start_v_2_' // dum, global_start )
    6728 
    6729        CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, ldum, &
    6730                                          global_start )
    6731 
    6732        IF ( MAXVAL( surf_usm_v(l)%end_index ) <= 0 )  CYCLE
    6733 
    6734        IF ( .NOT. ALLOCATED( t_wall_v_1(l)%val ) )                                                   &
     6723       CALL rrd_mpi_io( 'usm_global_start_v_2_' // dum, global_start_index )
     6724       CALL rrd_mpi_io( 'usm_global_end_v_2_' // dum, global_end_index )
     6725
     6726       CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index,       &
     6727                                         data_to_read, global_start_index, global_end_index )
     6728       IF ( .NOT. data_to_read )  CYCLE
     6729
     6730       IF ( .NOT. ALLOCATED( t_wall_v_1(l)%val ) )                                                 &
    67356731          ALLOCATE ( t_wall_v_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    67366732       CALL rrd_mpi_io_surface( 't_wall_v(' // dum // ')', t_wall_v_1(l)%val )
    67376733
    6738        IF ( .NOT. ALLOCATED( t_window_v_1(l)%val ) )                                                 &
     6734       IF ( .NOT. ALLOCATED( t_window_v_1(l)%val ) )                                               &
    67396735          ALLOCATE ( t_window_v_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    67406736       CALL rrd_mpi_io_surface( 't_window_v(' // dum // ')', t_window_v_1(l)%val )
    67416737
    6742        IF ( .NOT. ALLOCATED( t_green_v_1(l)%val ) )                                                  &
     6738       IF ( .NOT. ALLOCATED( t_green_v_1(l)%val ) )                                                &
    67436739          ALLOCATE ( t_green_v_1(l)%val(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    67446740       CALL rrd_mpi_io_surface( 't_green_v(' // dum // ')', t_green_v_1(l)%val )
     
    67476743
    67486744 END SUBROUTINE usm_rrd_local_mpi
     6745
    67496746
    67506747!--------------------------------------------------------------------------------------------------!
     
    74227419    INTEGER(iwp)  ::  l  !< index surface type orientation
    74237420
    7424     INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr)  ::  global_start_index  !< index for surface data (MPI-IO)
     7421    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_end_index    !< end index for surface data (MPI-IO)
     7422    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< start index for surface data (MPI-IO)
    74257423
    74267424    LOGICAL  ::  surface_data_to_write  !< switch for MPI-I/O if PE has surface data to write
     
    75487546          WRITE( dum, '(I1)')  l
    75497547
    7550           CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,             &
    7551                                             surface_data_to_write, global_start_index )
    7552 
    7553           CALL wrd_mpi_io( 'usm_start_index_h_' // dum,  surf_usm_h(l)%start_index )
    7554           CALL wrd_mpi_io( 'usm_end_index_h_' // dum, surf_usm_h(l)%end_index )
     7548          CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,    &
     7549                                            surface_data_to_write, global_start_index,             &
     7550                                            global_end_index )
     7551
    75557552          CALL wrd_mpi_io( 'usm_global_start_h_' // dum, global_start_index )
     7553          CALL wrd_mpi_io( 'usm_global_end_h_' // dum, global_end_index )
    75567554
    75577555          IF ( .NOT. surface_data_to_write )  CYCLE
     
    75747572
    75757573          CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index,    &
    7576                                             surface_data_to_write, global_start_index )
    7577 
    7578           CALL wrd_mpi_io( 'usm_start_index_v_' // dum, surf_usm_v(l)%start_index )
    7579           CALL wrd_mpi_io( 'usm_end_index_v_' // dum, surf_usm_v(l)%end_index )
     7574                                            surface_data_to_write, global_start_index,             &
     7575                                            global_end_index )
     7576
    75807577          CALL wrd_mpi_io( 'usm_global_start_v_' // dum, global_start_index )
     7578          CALL wrd_mpi_io( 'usm_global_end_v_' // dum,   global_end_index )
    75817579
    75827580          IF ( .NOT. surface_data_to_write )  CYCLE
     
    75967594          WRITE( dum, '(I1)')  l
    75977595
    7598           CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,             &
    7599                                             surface_data_to_write, global_start_index )
    7600 
    7601           CALL wrd_mpi_io( 'usm_start_index_h_2_' // dum,  surf_usm_h(l)%start_index )
    7602           CALL wrd_mpi_io( 'usm_end_index_h_2_' // dum, surf_usm_h(l)%end_index )
     7596          CALL rd_mpi_io_surface_filetypes( surf_usm_h(l)%start_index, surf_usm_h(l)%end_index,    &
     7597                                            surface_data_to_write, global_start_index,             &
     7598                                            global_end_index )
     7599
    76037600          CALL wrd_mpi_io( 'usm_global_start_h_2_' // dum, global_start_index )
     7601          CALL wrd_mpi_io( 'usm_global_end_h_2_' // dum, global_end_index )
    76047602
    76057603          IF ( .NOT. surface_data_to_write )  CYCLE
     
    76167614
    76177615          CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index,    &
    7618                                             surface_data_to_write, global_start_index )
    7619 
    7620           CALL wrd_mpi_io( 'usm_start_index_v_2_' //dum, surf_usm_v(l)%start_index )
    7621           CALL wrd_mpi_io( 'usm_end_index_v_2_' // dum, surf_usm_v(l)%end_index )
     7616                                            surface_data_to_write, global_start_index,             &
     7617                                            global_end_index )
     7618
    76227619          CALL wrd_mpi_io( 'usm_global_start_v_2_' // dum, global_start_index )
     7620          CALL wrd_mpi_io( 'usm_global_end_v_2_' // dum, global_end_index )
    76237621
    76247622          IF ( .NOT. surface_data_to_write )  CYCLE
Note: See TracChangeset for help on using the changeset viewer.