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

    r4511 r4517  
    2727! -----------------
    2828! $Id$
     29! added restart with MPI-IO
     30!
     31! 4511 2020-04-30 12:20:40Z raasch
    2932! decycling replaced by explicit setting of lateral boundary conditions
    3033!
     
    312315                max_pr_user,                                                                       &
    313316                monotonic_limiter_z,                                                               &
     317                restart_data_format_output,                                                        &
    314318                scalar_advec,                                                                      &
    315319                timestep_scheme, use_prescribed_profile_data, ws_scheme_sca, air_chemistry
     
    329333    USE cpulog,                                                                                    &
    330334        ONLY:  cpu_log, log_point_s
     335
     336    USE restart_data_mpi_io_mod,                                                                   &
     337        ONLY:  rrd_mpi_io, wrd_mpi_io
    331338
    332339    USE statistics
     
    501508
    502509    INTERFACE chem_rrd_local
    503        MODULE PROCEDURE chem_rrd_local
     510       MODULE PROCEDURE chem_rrd_local_ftn
     511       MODULE PROCEDURE chem_rrd_local_mpi
    504512    END INTERFACE chem_rrd_local
    505513
     
    30423050! Description:
    30433051! ------------
    3044 !> Subroutine to read restart data of chemical species
    3045 !------------------------------------------------------------------------------!
    3046  SUBROUTINE chem_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,             &
    3047                             nxr_on_file, nynf, nync, nyn_on_file, nysf, nysc,   &
    3048                             nys_on_file, tmp_3d, found )
     3052!> Read module-specific local restart data arrays (Fortran binary format).
     3053!------------------------------------------------------------------------------!
     3054 SUBROUTINE chem_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,             &
     3055                                nxr_on_file, nynf, nync, nyn_on_file, nysf, nysc,   &
     3056                                nys_on_file, tmp_3d, found )
    30493057
    30503058    USE control_parameters
     
    30763084
    30773085
    3078     IF ( ALLOCATED(chem_species) )  THEN
     3086    IF ( ALLOCATED( chem_species ) )  THEN
    30793087
    30803088       DO  lsp = 1, nspec
     
    31053113
    31063114
    3107  END SUBROUTINE chem_rrd_local
     3115 END SUBROUTINE chem_rrd_local_ftn
     3116
     3117
     3118!------------------------------------------------------------------------------!
     3119! Description:
     3120! ------------
     3121!> Read module-specific local restart data arrays (Fortran binary format).
     3122!------------------------------------------------------------------------------!
     3123 SUBROUTINE chem_rrd_local_mpi
     3124
     3125    IMPLICIT NONE
     3126
     3127    INTEGER(iwp) ::  lsp !<
     3128
     3129    IF ( ALLOCATED( chem_species ) )  THEN
     3130
     3131       DO  lsp = 1, nspec
     3132
     3133          CALL rrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc )
     3134          CALL rrd_mpi_io( TRIM( chem_species(lsp)%name )//'_av', chem_species(lsp)%conc_av )
     3135
     3136       ENDDO
     3137
     3138    ENDIF
     3139
     3140 END SUBROUTINE chem_rrd_local_mpi
    31083141
    31093142
     
    32083241    INTEGER(iwp) ::  lsp  !< running index for chem spcs.
    32093242
    3210     DO  lsp = 1, nspec
    3211        CALL wrd_write_string( TRIM( chem_species(lsp)%name ) )
    3212        WRITE ( 14 )  chem_species(lsp)%conc
    3213        CALL wrd_write_string( TRIM( chem_species(lsp)%name )//'_av' )
    3214        WRITE ( 14 )  chem_species(lsp)%conc_av
    3215     ENDDO
     3243    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     3244
     3245       DO  lsp = 1, nspec
     3246          CALL wrd_write_string( TRIM( chem_species(lsp)%name ) )
     3247          WRITE ( 14 )  chem_species(lsp)%conc
     3248          CALL wrd_write_string( TRIM( chem_species(lsp)%name )//'_av' )
     3249          WRITE ( 14 )  chem_species(lsp)%conc_av
     3250       ENDDO
     3251
     3252    ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     3253
     3254       DO  lsp = 1, nspec
     3255          CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc )
     3256          CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ) // '_av', chem_species(lsp)%conc_av )
     3257       ENDDO
     3258
     3259    ENDIF
    32163260
    32173261 END SUBROUTINE chem_wrd_local
Note: See TracChangeset for help on using the changeset viewer.