Ignore:
Timestamp:
Apr 13, 2020 8:11:20 PM (4 years ago)
Author:
raasch
Message:

restart data handling with MPI-IO added, first part

File:
1 edited

Legend:

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

    r4360 r4495  
    2525! -----------------
    2626! $Id$
     27! restart data handling with MPI-IO added
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    4750 MODULE flight_mod
    4851 
    49     USE control_parameters,                                                    &
    50         ONLY:  debug_output, fl_max, num_leg, num_var_fl, num_var_fl_user, virtual_flight
     52    USE control_parameters,                                                                        &
     53        ONLY:  debug_output, fl_max, num_leg, num_var_fl, num_var_fl_user,                         &
     54               restart_data_format_output, virtual_flight
    5155 
    5256    USE kinds
     57
     58    USE restart_data_mpi_io_mod,                                                                   &
     59        ONLY:  rd_mpi_io_check_array, rrd_mpi_io_global_array, wrd_mpi_io_global_array
     60
    5361
    5462    CHARACTER(LEN=6), DIMENSION(fl_max) ::  leg_mode = 'cyclic'  !< flight mode through the model domain, either 'cyclic' or 'return'
     
    117125   
    118126    INTERFACE flight_rrd_global
    119        MODULE PROCEDURE flight_rrd_global
     127       MODULE PROCEDURE flight_rrd_global_ftn
     128       MODULE PROCEDURE flight_rrd_global_mpi
    120129    END INTERFACE flight_rrd_global
    121130   
     
    919928! Description:
    920929! ------------
    921 !> This routine reads the respective restart data.
    922 !------------------------------------------------------------------------------!
    923     SUBROUTINE flight_rrd_global( found ) 
     930!> Read module-specific global restart data (Fortran binary format).
     931!------------------------------------------------------------------------------!
     932    SUBROUTINE flight_rrd_global_ftn( found )
    924933
    925934
     
    964973
    965974
    966     END SUBROUTINE flight_rrd_global 
     975    END SUBROUTINE flight_rrd_global_ftn
     976
     977
     978!------------------------------------------------------------------------------!
     979! Description:
     980! ------------
     981!> Read module-specific global restart data (MPI-IO).
     982!------------------------------------------------------------------------------!
     983    SUBROUTINE flight_rrd_global_mpi
     984
     985
     986       IMPLICIT NONE
     987
     988       LOGICAL  ::  array_found  !< flag indicating if respective array is found in restart file
     989
     990
     991       CALL rd_mpi_io_check_array( 'u_agl', found = array_found )
     992       IF ( array_found)  THEN
     993          IF ( .NOT. ALLOCATED( u_agl ) )  ALLOCATE( u_agl(1:num_leg) )
     994          CALL rrd_mpi_io_global_array( 'u_agl', u_agl )
     995       ENDIF
     996       CALL rd_mpi_io_check_array( 'v_agl', found = array_found )
     997       IF ( array_found)  THEN
     998          IF ( .NOT. ALLOCATED( v_agl ) )  ALLOCATE( v_agl(1:num_leg) )
     999          CALL rrd_mpi_io_global_array( 'v_agl', v_agl )
     1000       ENDIF
     1001       CALL rd_mpi_io_check_array( 'w_agl', found = array_found )
     1002       IF ( array_found)  THEN
     1003          IF ( .NOT. ALLOCATED( w_agl ) )  ALLOCATE( w_agl(1:num_leg) )
     1004          CALL rrd_mpi_io_global_array( 'w_agl', w_agl )
     1005       ENDIF
     1006       CALL rd_mpi_io_check_array( 'x_pos', found = array_found )
     1007       IF ( array_found)  THEN
     1008          IF ( .NOT. ALLOCATED( x_pos ) )  ALLOCATE( x_pos(1:num_leg) )
     1009          CALL rrd_mpi_io_global_array( 'x_pos', x_pos )
     1010       ENDIF
     1011       CALL rd_mpi_io_check_array( 'y_pos', found = array_found )
     1012       IF ( array_found)  THEN
     1013          IF ( .NOT. ALLOCATED( y_pos ) )  ALLOCATE( y_pos(1:num_leg) )
     1014          CALL rrd_mpi_io_global_array( 'y_pos', y_pos )
     1015       ENDIF
     1016       CALL rd_mpi_io_check_array( 'z_pos', found = array_found )
     1017       IF ( array_found)  THEN
     1018          IF ( .NOT. ALLOCATED( z_pos ) )  ALLOCATE( z_pos(1:num_leg) )
     1019          CALL rrd_mpi_io_global_array( 'z_pos', z_pos )
     1020       ENDIF
     1021
     1022    END SUBROUTINE flight_rrd_global_mpi
     1023
    9671024   
    9681025!------------------------------------------------------------------------------!
     
    9761033       IMPLICIT NONE
    9771034 
    978        CALL wrd_write_string( 'u_agl' )
    979        WRITE ( 14 )  u_agl
    980 
    981        CALL wrd_write_string( 'v_agl' )
    982 
    983        WRITE ( 14 )  v_agl
    984 
    985        CALL wrd_write_string( 'w_agl' )
    986        WRITE ( 14 )  w_agl
    987 
    988        CALL wrd_write_string( 'x_pos' )
    989        WRITE ( 14 )  x_pos
    990 
    991        CALL wrd_write_string( 'y_pos' )
    992        WRITE ( 14 )  y_pos
    993 
    994        CALL wrd_write_string( 'z_pos' )
    995        WRITE ( 14 )  z_pos
    996        
     1035
     1036       IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1037
     1038          CALL wrd_write_string( 'u_agl' )
     1039          WRITE ( 14 )  u_agl
     1040
     1041          CALL wrd_write_string( 'v_agl' )
     1042          WRITE ( 14 )  v_agl
     1043
     1044          CALL wrd_write_string( 'w_agl' )
     1045          WRITE ( 14 )  w_agl
     1046
     1047          CALL wrd_write_string( 'x_pos' )
     1048          WRITE ( 14 )  x_pos
     1049
     1050          CALL wrd_write_string( 'y_pos' )
     1051          WRITE ( 14 )  y_pos
     1052
     1053          CALL wrd_write_string( 'z_pos' )
     1054          WRITE ( 14 )  z_pos
     1055
     1056       ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     1057
     1058          CALL wrd_mpi_io_global_array( 'u_agl', u_agl )
     1059          CALL wrd_mpi_io_global_array( 'v_agl', v_agl )
     1060          CALL wrd_mpi_io_global_array( 'w_agl', w_agl )
     1061          CALL wrd_mpi_io_global_array( 'x_pos', x_pos )
     1062          CALL wrd_mpi_io_global_array( 'y_pos', y_pos )
     1063          CALL wrd_mpi_io_global_array( 'z_pos', z_pos )
     1064
     1065       ENDIF
     1066
    9971067    END SUBROUTINE flight_wrd_global   
    9981068   
Note: See TracChangeset for help on using the changeset viewer.