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

    r4876 r4893  
    2424! -----------------
    2525! $Id$
     26! revised output of surface data via MPI-IO for better performance
     27!
     28! 4876 2021-02-17 12:27:36Z raasch
    2629! bugfix for instantaneous c_liq output
    2730!
     
    62496252    INTEGER(iwp)      ::  l      !< index variable for surface orientation
    62506253
    6251     INTEGER(iwp),DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< index for surface data (MPI-IO)
     6254    INTEGER(iwp),DIMENSION(nys:nyn,nxl:nxr) ::  global_end_index    !< end index for surface data (MPI-IO)
     6255    INTEGER(iwp),DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< start index for surface data (MPI-IO)
    62526256
    62536257    LOGICAL ::  surface_data_to_write  !< switch for MPI-I/O if PE has surface data to write
     
    64356439
    64366440          CALL rd_mpi_io_surface_filetypes( surf_lsm_h(l)%start_index, surf_lsm_h(l)%end_index,    &
    6437                                             surface_data_to_write, global_start_index )
    6438 
    6439           CALL wrd_mpi_io( 'lsm_start_index_h_' // dum,  surf_lsm_h(l)%start_index )
    6440           CALL wrd_mpi_io( 'lsm_end_index_h_' // dum,  surf_lsm_h(l)%end_index )
     6441                                            surface_data_to_write, global_start_index,             &
     6442                                            global_end_index )
     6443
    64416444          CALL wrd_mpi_io( 'lsm_global_start_index_h_' // dum, global_start_index )
     6445          CALL wrd_mpi_io( 'lsm_global_end_index_h_' // dum, global_end_index )
    64426446
    64436447          IF ( .NOT. surface_data_to_write )  CYCLE
    64446448
    64456449          CALL wrd_mpi_io_surface( 't_soil_h(' // dum // ')', t_soil_h(l)%var_2d )
    6446           CALL wrd_mpi_io_surface( 'm_soil_h(' // dum // ')',  m_soil_h(l)%var_2d )
     6450          CALL wrd_mpi_io_surface( 'm_soil_h(' // dum // ')', m_soil_h(l)%var_2d )
    64476451          CALL wrd_mpi_io_surface( 'm_liq_h(' // dum // ')', m_liq_h(l)%var_1d )
    64486452          CALL wrd_mpi_io_surface( 't_surface_h(' // dum // ')', t_surface_h(l)%var_1d )
     
    64546458
    64556459          CALL rd_mpi_io_surface_filetypes ( surf_lsm_v(l)%start_index, surf_lsm_v(l)%end_index,   &
    6456                                              surface_data_to_write, global_start_index )
    6457 
    6458           CALL wrd_mpi_io( 'lsm_start_index_v_' // dum,  surf_lsm_v(l)%start_index )
    6459           CALL wrd_mpi_io( 'lsm_end_index_v_' // dum,  surf_lsm_v(l)%end_index )
    6460           CALL wrd_mpi_io( 'lsm_global_start_index_v_' // dum , global_start_index )
     6460                                            surface_data_to_write, global_start_index,             &
     6461                                            global_end_index )
     6462
     6463          CALL wrd_mpi_io( 'lsm_global_start_index_v_' // dum, global_start_index )
     6464          CALL wrd_mpi_io( 'lsm_global_end_index_v_' // dum, global_end_index )
    64616465
    64626466          IF ( .NOT. surface_data_to_write )  CYCLE
     
    71337137    INTEGER(iwp) ::  l   !< running index surface orientation
    71347138
    7135     !INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  end_index
    7136     INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start
    7137     !INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  start_index
    7138 
    7139     LOGICAL      :: array_found
    7140     LOGICAL      :: ldum
     7139    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_end_index
     7140    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index
     7141
     7142    LOGICAL ::  array_found
     7143    LOGICAL ::  data_to_read    !< switch to steer reading of data
    71417144
    71427145
     
    72057208       WRITE( dum, '(I1)')  l
    72067209
    7207        CALL rrd_mpi_io( 'lsm_start_index_h_' // dum,  surf_lsm_h(l)%start_index )
    7208        CALL rrd_mpi_io( 'lsm_end_index_h_' // dum,  surf_lsm_h(l)%end_index )
    7209        CALL rrd_mpi_io( 'lsm_global_start_index_h_' // dum, global_start )
    7210 
    7211        CALL rd_mpi_io_surface_filetypes ( surf_lsm_h(l)%start_index, surf_lsm_h(l)%end_index, ldum,&
    7212                                           global_start )
    7213 
    7214        IF ( MAXVAL( surf_lsm_h(l)%end_index ) <= 0 )  CYCLE
     7210!
     7211!--    surf_lsm_h(l)%start_index and surf_lsm_h(l)%end_index are already set and should not be read
     7212!--    from restart file.
     7213       CALL rrd_mpi_io( 'lsm_global_start_index_h_' // dum, global_start_index )
     7214       CALL rrd_mpi_io( 'lsm_global_end_index_h_' // dum, global_end_index )
     7215
     7216       CALL rd_mpi_io_surface_filetypes ( surf_lsm_h(l)%start_index, surf_lsm_h(l)%end_index,      &
     7217                                          data_to_read, global_start_index, global_end_index )
     7218       IF ( .NOT. data_to_read )  CYCLE
    72157219
    72167220       CALL rrd_mpi_io_surface( 't_soil_h(' // dum // ')', t_soil_h(l)%var_2d )
     
    72187222       CALL rrd_mpi_io_surface( 'm_liq_h(' // dum // ')', m_liq_h(l)%var_1d )
    72197223       CALL rrd_mpi_io_surface( 't_surface_h(' // dum // ')', t_surface_h(l)%var_1d )
     7224
    72207225    ENDDO
    72217226
     
    72247229       WRITE( dum, '(I1)')  l
    72257230
    7226 !kk    In case of nothing to do, the settings of start_index and end_index differ
    7227 !kk    between writing and reading restart file
    7228 !kk
    7229 !kk    Has to be discussed with the developers
    7230 
    7231        CALL rrd_mpi_io( 'lsm_start_index_v_' // dum,  surf_lsm_v(l)%start_index )
    7232        CALL rrd_mpi_io( 'lsm_end_index_v_' // dum,  surf_lsm_v(l)%end_index )
    7233        CALL rrd_mpi_io( 'lsm_global_start_index_v_' // dum , global_start )
    7234 
    7235        CALL rd_mpi_io_surface_filetypes( surf_lsm_v(l)%start_index, surf_lsm_v(l)%end_index, ldum, &
    7236                                          global_start )
    7237 
    7238        IF ( MAXVAL( surf_lsm_v(l)%end_index ) <= 0 )  CYCLE
     7231!
     7232!--    surf_lsm_v(l)%start_index and surf_lsm_v(l)%end_index are already set and should not be read
     7233!--    from restart file.
     7234       CALL rrd_mpi_io( 'lsm_global_start_index_v_' // dum , global_start_index )
     7235       CALL rrd_mpi_io( 'lsm_global_end_index_v_' // dum , global_end_index )
     7236
     7237       CALL rd_mpi_io_surface_filetypes( surf_lsm_v(l)%start_index, surf_lsm_v(l)%end_index,       &
     7238                                         data_to_read, global_start_index, global_end_index )
     7239       IF ( .NOT. data_to_read )  CYCLE
    72397240
    72407241       CALL rrd_mpi_io_surface( 't_soil_v(' // dum // ')', t_soil_v(l)%var_2d )
Note: See TracChangeset for help on using the changeset viewer.