Ignore:
Timestamp:
Jun 29, 2020 7:54:21 AM (4 years ago)
Author:
raasch
Message:

bugfix for aborts in case of nested runs, data handling with MPI-IO for cyclic-fill added (so far only for global data)

File:
1 edited

Legend:

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

    r4564 r4580  
    2525! -----------------
    2626! $Id$
     27! data handling with MPI-IO for cyclic-fill added (so far only for global data)
     28!
     29! 4564 2020-06-12 14:03:36Z raasch
    2730! Vertical nesting method of Huq et al. (2019) removed
    2831!
     
    11651168!> (initializing_actions  == 'cyclic_fill').
    11661169!------------------------------------------------------------------------------!
    1167 
    1168     SUBROUTINE rrd_read_parts_of_global
    1169 
    1170 
    1171        CHARACTER (LEN=10) ::  version_on_file
    1172        CHARACTER (LEN=20) ::  momentum_advec_check
    1173        CHARACTER (LEN=20) ::  scalar_advec_check
    1174        CHARACTER (LEN=1)  ::  cdum
    1175 
    1176        INTEGER(iwp) ::  max_pr_user_on_file
    1177        INTEGER(iwp) ::  nz_on_file
    1178        INTEGER(iwp) ::  statistic_regions_on_file
    1179        INTEGER(iwp) ::  tmp_mpru
    1180        INTEGER(iwp) ::  tmp_sr
    1181 
    1182        REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
    1183        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
    1184 
    1185 
     1170 SUBROUTINE rrd_read_parts_of_global
     1171
     1172
     1173    CHARACTER (LEN=10) ::  version_on_file
     1174    CHARACTER (LEN=20) ::  momentum_advec_check
     1175    CHARACTER (LEN=20) ::  scalar_advec_check
     1176    CHARACTER (LEN=1)  ::  cdum
     1177
     1178    INTEGER(iwp) ::  max_pr_user_on_file
     1179    INTEGER(iwp) ::  nz_on_file
     1180    INTEGER(iwp) ::  statistic_regions_on_file
     1181    INTEGER(iwp) ::  tmp_mpru
     1182    INTEGER(iwp) ::  tmp_sr
     1183
     1184    REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
     1185    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
     1186
     1187
     1188    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
     1189!
     1190!--    Input in Fortran binary format
    11861191       CALL check_open( 13 )
    11871192
     
    11911196
    11921197!
    1193 !-- Read number of PEs and horizontal index bounds of all PEs used in previous
    1194 !-- run
     1198!--    Read number of PEs and horizontal index bounds of all PEs used in previous run
    11951199       READ ( 13 )  length
    11961200       READ ( 13 )  restart_string(1:length)
     
    12181222
    12191223!
    1220 !-- Read vertical number of gridpoints and number of different areas used
    1221 !-- for computing statistics. Allocate arrays depending on these values,
    1222 !-- which are needed for the following read instructions.
     1224!--    Read vertical number of gridpoints and number of different areas used for computing
     1225!--    statistics. Allocate arrays depending on these values, which are needed for the following
     1226!--   read instructions.
    12231227       READ ( 13 )  length
    12241228       READ ( 13 )  restart_string(1:length)
     
    12811285
    12821286!
    1283 !-- Now read and check some control parameters and skip the rest
     1287!--    Now read and check some control parameters and skip the rest
    12841288       READ ( 13 )  length
    12851289       READ ( 13 )  restart_string(1:length)
     
    13601364       ENDDO
    13611365
     1366       CALL close_file( 13 )
     1367
     1368    ELSEIF ( restart_data_format_input(1:3) == 'mpi' )  THEN
     1369!
     1370!--    Open the MPI-IO restart file.
     1371       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ),                              &
     1372                            open_for_global_io_only = .TRUE. )
     1373
     1374!
     1375!--    Read vertical number of gridpoints and number of different areas used for computing
     1376!--    statistics. Allocate arrays depending on these values, which are required for the following
     1377!--    read instructions.
     1378       CALL rrd_mpi_io( 'nz', nz_on_file )
     1379       IF ( nz_on_file /= nz )  THEN
     1380          WRITE( message_string, * ) 'mismatch concerning number of gridpoints along z:',          &
     1381                                     '&nz on file    = "', nz_on_file, '"',                        &
     1382                                     '&nz from run   = "', nz, '"'
     1383          CALL message( 'rrd_read_parts_of_global', 'PA0304', 1, 2, 0, 6, 0 )
     1384       ENDIF
     1385
     1386       CALL rrd_mpi_io( 'max_pr_user', max_pr_user_on_file )
     1387       IF ( max_pr_user_on_file /= max_pr_user )  THEN
     1388          WRITE( message_string, * ) 'number of user profiles on restart data file differs from ', &
     1389                                     'the current run:&max_pr_user on file    = "',                &
     1390                                     max_pr_user_on_file, '" &max_pr_user from run   = "',         &
     1391                                     max_pr_user, '"'
     1392          CALL message( 'rrd_read_parts_of_global', 'PA0306', 0, 0, 0, 6, 0 )
     1393          tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
     1394       ELSE
     1395          tmp_mpru = max_pr_user
     1396       ENDIF
     1397
     1398       CALL rrd_mpi_io( 'statistic_regions', statistic_regions_on_file )
     1399       IF ( statistic_regions_on_file /= statistic_regions )  THEN
     1400          WRITE( message_string, * ) 'statistic regions on restart data file ',&
     1401                                     'differ from the current run:',           &
     1402                                     '&statistic regions on file    = "',      &
     1403                                     statistic_regions_on_file, '"',           &
     1404                                     '&statistic regions from run   = "',      &
     1405                                      statistic_regions, '"',                  &
     1406                                     '&statistic data may be lost!'
     1407          CALL message( 'rrd_read_parts_of_global', 'PA0308', 0, 1, 0, 6, 0 )
     1408          tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
     1409       ELSE
     1410          tmp_sr = statistic_regions
     1411       ENDIF
     1412
     1413!
     1414!--    Now read and check some control parameters and skip the rest.
     1415       CALL rrd_mpi_io( 'average_count_pr', average_count_pr )
     1416       IF ( average_count_pr /= 0 )  THEN
     1417          WRITE( message_string, * ) 'inflow profiles not ',          &
     1418                         'temporally averaged. &Averaging will be ',  &
     1419                         'done now using', average_count_pr,          &
     1420                         ' samples.'
     1421          CALL message( 'rrd_read_parts_of_global', 'PA0309', 0, 1, 0, 6, 0 )
     1422       ENDIF
     1423
     1424       ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file,0:statistic_regions_on_file) )
     1425       CALL rrd_mpi_io_global_array( 'hom', hom_on_file )
     1426       hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
     1427       DEALLOCATE( hom_on_file )
     1428
     1429       ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, 0:statistic_regions_on_file) )
     1430       CALL rrd_mpi_io_global_array( 'hom_sum', hom_sum_on_file )
     1431       hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
     1432       DEALLOCATE( hom_sum_on_file )
     1433
     1434       momentum_advec_check = momentum_advec
     1435       CALL rrd_mpi_io( 'momentum_advec', momentum_advec )
     1436       IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  THEN
     1437          WRITE( message_string, * ) 'momentum_advec of the restart ',&
     1438                                  'run differs from momentum_advec of the ',   &
     1439                                  'initial run.'
     1440          CALL message( 'rrd_read_parts_of_global', 'PA0100', 1, 2, 0, 6, 0 )
     1441       ENDIF
     1442
     1443       CALL rrd_mpi_io( 'nx', nx_on_file )
     1444       CALL rrd_mpi_io( 'ny', ny_on_file )
     1445       CALL rrd_mpi_io_global_array( 'ref_state', ref_state )
     1446
     1447       scalar_advec_check = scalar_advec
     1448       CALL rrd_mpi_io( 'scalar_advec', scalar_advec )
     1449       IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )  THEN
     1450          WRITE( message_string, * ) 'scalar_advec of the restart ',  &
     1451                                  'run differs from scalar_advec of the ',     &
     1452                                  'initial run.'
     1453          CALL message( 'rrd_read_parts_of_global', 'PA0101', 1, 2, 0, 6, 0 )
     1454       ENDIF
     1455
     1456!
     1457!--    Close restart file
     1458       CALL rd_mpi_io_close
     1459
     1460    ENDIF
     1461
    13621462!
    13631463!-- Calculate the temporal average of vertical profiles, if neccessary
     
    13661466    ENDIF
    13671467
    1368 
    1369     CALL close_file( 13 )
    1370 
    1371 
    1372     END SUBROUTINE rrd_read_parts_of_global
     1468 END SUBROUTINE rrd_read_parts_of_global
    13731469
    13741470
     
    14471543
    14481544!
    1449 !--    Allocate temporary buffer arrays. In previous versions, there were
     1545!--    Allocate temporary buffer arrays. In previous versions, they were
    14501546!--    declared as automated arrays, causing memory problems when these
    14511547!--    were allocate on stack.
Note: See TracChangeset for help on using the changeset viewer.