Ignore:
Timestamp:
May 3, 2020 2:29:30 PM (4 years ago)
Author:
raasch
Message:

added restart with MPI-IO for reading local arrays

File:
1 edited

Legend:

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

    r4510 r4517  
    2727! -----------------
    2828! $Id$
     29! added restart with MPI-IO for reading local arrays
     30!
     31! 4510 2020-04-29 14:19:18Z raasch
    2932! Further re-formatting to follow the PALM coding standard
    3033!
     
    368371    USE restart_data_mpi_io_mod,                                                                   &
    369372        ONLY:  rd_mpi_io_surface_filetypes,                                                        &
     373               rrd_mpi_io,                                                                         &
     374               rrd_mpi_io_surface,                                                                 &
    370375               wrd_mpi_io,                                                                         &
    371376               wrd_mpi_io_surface
     
    617622
    618623
    619 
    620 
    621624!
    622625!-- Building facade/wall/green/window properties (partly according to PIDS).
     
    840843
    841844    INTERFACE usm_rrd_local
    842        MODULE PROCEDURE usm_rrd_local
     845       MODULE PROCEDURE usm_rrd_local_ftn
     846       MODULE PROCEDURE usm_rrd_local_mpi
    843847    END INTERFACE usm_rrd_local
    844848
     
    61106114! Description:
    61116115! ------------
    6112 !> Soubroutine reads t_surf and t_wall data from restart files
     6116!> Read module-specific local restart data arrays (Fortran binary format).
     6117!> Soubroutine reads t_surf and t_wall.
    61136118!--------------------------------------------------------------------------------------------------!
    6114  SUBROUTINE usm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,       &
    6115                            nysf, nysc, nys_on_file, found )
     6119 SUBROUTINE usm_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,   &
     6120                               nysf, nysc, nys_on_file, found )
    61166121
    61176122
     
    66546659    END SELECT
    66556660
    6656  END SUBROUTINE usm_rrd_local
     6661 END SUBROUTINE usm_rrd_local_ftn
     6662
     6663
     6664!--------------------------------------------------------------------------------------------------!
     6665! Description:
     6666! ------------
     6667!> Read module-specific local restart data arrays (MPI-IO).
     6668!> Soubroutine reads t_surf and t_wall.
     6669!>
     6670!> This read routine is a counterpart of usm_wrd_local.
     6671!> In usm_wrd_local, all array are unconditionally written, therefore all arrays are read here.
     6672!> This is a preliminary version of reading usm data. The final version has to be discussed with
     6673!> the developers.
     6674!>
     6675!> If it is possible to call usm_allocate_surface before reading the restart file, this reading
     6676!> routine would become much simpler, because no checking for allocation will be necessary any more.
     6677!--------------------------------------------------------------------------------------------------!
     6678 SUBROUTINE usm_rrd_local_mpi
     6679
     6680
     6681    CHARACTER(LEN=1) ::  dum  !< dummy string to create input-variable name
     6682
     6683    INTEGER(iwp) ::  l  !< loop index for surface types
     6684
     6685    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start
     6686
     6687    LOGICAL ::  ldum  !< dummy variable
     6688
     6689
     6690    CALL rrd_mpi_io( 'usm_start_index_h',  surf_usm_h%start_index )
     6691    CALL rrd_mpi_io( 'usm_end_index_h', surf_usm_h%end_index )
     6692    CALL rrd_mpi_io( 'usm_global_start_h', global_start )
     6693
     6694    CALL rd_mpi_io_surface_filetypes( surf_usm_h%start_index, surf_usm_h%end_index, ldum,          &
     6695                                      global_start )
     6696
     6697    IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )  ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
     6698    CALL rrd_mpi_io_surface( 't_surf_wall_h', t_surf_wall_h_1 )
     6699
     6700    IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )  ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
     6701    CALL rrd_mpi_io_surface( 't_surf_window_h', t_surf_window_h_1 )
     6702
     6703    IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )  ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
     6704    CALL rrd_mpi_io_surface( 't_surf_green_h', t_surf_green_h_1 )
     6705
     6706    DO  l = 0, 3
     6707
     6708       WRITE( dum, '(I1)' )  l
     6709
     6710       CALL rrd_mpi_io( 'usm_start_index_v_' //dum, surf_usm_v(l)%start_index )
     6711       CALL rrd_mpi_io( 'usm_end_index_v_' // dum, surf_usm_v(l)%end_index )
     6712       CALL rrd_mpi_io( 'usm_global_start_v_' // dum, global_start )
     6713
     6714       CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, ldum, &
     6715                                         global_start )
     6716
     6717       IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(l)%t ) )                                             &
     6718          ALLOCATE( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
     6719       CALL rrd_mpi_io_surface( 't_surf_wall_v(' // dum // ')', t_surf_wall_v_1(l)%t )
     6720
     6721       IF ( .NOT.  ALLOCATED( t_surf_window_v_1(l)%t ) )                                           &
     6722          ALLOCATE( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
     6723       CALL rrd_mpi_io_surface( 't_surf_window_v(' // dum // ')', t_surf_window_v_1(l)%t )
     6724
     6725       IF ( .NOT.  ALLOCATED( t_surf_green_v_1(l)%t ) )                                            &
     6726          ALLOCATE( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
     6727       CALL rrd_mpi_io_surface( 't_surf_green_v(' // dum // ')', t_surf_green_v_1(l)%t)
     6728
     6729    ENDDO
     6730
     6731    CALL rrd_mpi_io( 'usm_start_index_h_2',  surf_usm_h%start_index )
     6732    CALL rrd_mpi_io( 'usm_end_index_h_2', surf_usm_h%end_index )
     6733    CALL rrd_mpi_io( 'usm_global_start_h_2', global_start )
     6734
     6735    CALL rd_mpi_io_surface_filetypes( surf_usm_h%start_index, surf_usm_h%end_index, ldum,          &
     6736                                      global_start )
     6737
     6738    IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                                                          &
     6739       ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
     6740    CALL rrd_mpi_io_surface( 't_wall_h', t_wall_h_1 )
     6741
     6742    IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                                                        &
     6743       ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
     6744    CALL rrd_mpi_io_surface( 't_window_h', t_window_h_1 )
     6745
     6746    IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                                                         &
     6747       ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
     6748    CALL rrd_mpi_io_surface( 't_green_h', t_green_h_1 )
     6749
     6750    DO  l = 0, 3
     6751
     6752       WRITE( dum, '(I1)' )  l
     6753
     6754       CALL rrd_mpi_io( 'usm_start_index_v_2_' //dum, surf_usm_v(l)%start_index )
     6755       CALL rrd_mpi_io( 'usm_end_index_v_2_' // dum, surf_usm_v(l)%end_index )
     6756       CALL rrd_mpi_io( 'usm_global_start_v_2_' // dum, global_start )
     6757
     6758       CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, ldum, &
     6759                                         global_start )
     6760
     6761       IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                                                   &
     6762          ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
     6763       CALL rrd_mpi_io_surface( 't_wall_v(' // dum // ')', t_wall_v_1(l)%t )
     6764
     6765       IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                                                 &
     6766          ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
     6767       CALL rrd_mpi_io_surface( 't_window_v(' // dum // ')', t_window_v_1(l)%t )
     6768
     6769       IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                                                  &
     6770          ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
     6771       CALL rrd_mpi_io_surface( 't_green_v(' // dum // ')', t_green_v_1(l)%t )
     6772
     6773    ENDDO
     6774
     6775 END SUBROUTINE usm_rrd_local_mpi
     6776
    66576777
    66586778
Note: See TracChangeset for help on using the changeset viewer.