Ignore:
Timestamp:
Jul 29, 2020 7:23:03 AM (4 years ago)
Author:
raasch
Message:

extensions required for MPI-I/O of particle data to restart files

File:
1 edited

Legend:

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

    r4616 r4628  
    2525! -----------------
    2626! $Id$
     27! extensions required for MPI-I/O of particle data to restart files
     28!
     29! 4616 2020-07-21 10:09:46Z schwenkel
    2730! Bugfix in case of strechting: k-calculation limited lower bound of 1
    2831!
     
    189192               child_domain,                                                   &
    190193               cloud_droplets, constant_flux_layer, current_timestep_number,   &
    191                dt_3d, dt_3d_reached, first_call_lpm, humidity,                 &
     194               dt_3d, dt_3d_reached, debug_output, first_call_lpm, humidity,   &
    192195               dt_3d_reached_l, dt_dopts, dz, initializing_actions,            &
    193196               intermediate_timestep_count, intermediate_timestep_count_max,   &
    194197               message_string, molecular_viscosity, ocean_mode,                &
    195                particle_maximum_age, restart_data_format_output,               &
     198               particle_maximum_age, restart_data_format_input,                &
     199               restart_data_format_output,                                     &
    196200               simulated_time, topography, dopts_time_count,                   &
    197201               time_since_reference_point, rho_surface, u_gtrans, v_gtrans,    &
     
    240244               id_random_array
    241245
    242     USE restart_data_mpi_io_mod,                                                                   &
    243         ONLY:  rd_mpi_io_check_array, rrd_mpi_io, wrd_mpi_io
     246    USE restart_data_mpi_io_mod,                                               &
     247        ONLY:  rd_mpi_io_check_array,                                          &
     248               rd_mpi_io_check_open,                                           &
     249               rd_mpi_io_close,                                                &
     250               rd_mpi_io_open,                                                 &
     251               rd_mpi_io_particle_filetypes,                                   &
     252               rrd_mpi_io,                                                     &
     253               rrd_mpi_io_global_array,                                        &
     254               rrd_mpi_io_particles,                                           &
     255               wrd_mpi_io,                                                     &
     256               wrd_mpi_io_global_array,                                        &
     257               wrd_mpi_io_particles
    244258
    245259    USE statistics,                                                            &
     
    251265               surf_lsm_h,                                                     &
    252266               surf_usm_h
     267
     268!-- Next lines are in preparation for the output of particle data
     269!    USE data_output_particle_mod,                                              &
     270!        ONLY:  dop_active, dop_init, dop_output_tseries
    253271
    254272#if defined( __parallel )  &&  !defined( __mpifh )
     
    594612       write_particle_statistics
    595613
    596        NAMELIST /particle_parameters/ &
     614    NAMELIST /particle_parameters/ &
    597615       aero_species, &
    598616       aero_type, &
     
    619637       na, &
    620638       number_concentration, &
     639       number_of_output_particles, &
    621640       number_of_particle_groups, &
    622641       number_particles_per_gridbox, &
     642       oversize, &
    623643       particles_per_point, &
    624644       particle_advection_start, &
    625645       particle_advection_interpolation, &
    626646       particle_maximum_age, &
     647       part_output, &
     648       part_inc, &
     649       part_percent, &
    627650       pdx, &
    628651       pdy, &
     
    648671       splitting_mode, &
    649672       step_dealloc, &
     673       unlimited_dimension, &
    650674       use_sgs_for_particles, &
    651675       vertical_particle_advection, &
     
    12151239!-- Initialize collision kernels
    12161240    IF ( collision_kernel /= 'none' )  CALL lpm_init_kernels
     1241
    12171242!
    12181243!-- For the first model run of a possible job chain initialize the
     
    12411266                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
    12421267                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
    1243                                       0, 0, 0_idp, .FALSE., -1 )
     1268                                      0, 0, 0_idp, .FALSE., -1, -1 )
    12441269
    12451270       particle_groups = particle_groups_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp )
     
    13041329    IF ( nested_run )  CALL pmcp_g_init
    13051330#endif
     1331
     1332!-- next line is in preparation for particle data output
     1333!    CALL dop_init
    13061334
    13071335!
     
    29953023 SUBROUTINE lpm_rrd_local_particles
    29963024
    2997     CHARACTER (LEN=10) ::  particle_binary_version    !<
    2998     CHARACTER (LEN=10) ::  version_on_file            !<
     3025    CHARACTER(LEN=10) ::  particle_binary_version    !<
     3026    CHARACTER(LEN=10) ::  version_on_file            !<
     3027
     3028    CHARACTER(LEN=20) ::  save_restart_data_format_input  !<
    29993029
    30003030    INTEGER(iwp) ::  alloc_size !<
     
    30033033    INTEGER(iwp) ::  kp         !<
    30043034
     3035    INTEGER(idp), ALLOCATABLE, DIMENSION(:,:,:) ::  prt_global_index !<
     3036
     3037    LOGICAL ::  save_debug_output  !<
     3038
    30053039    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  tmp_particles !<
    30063040
    3007 !
    3008 !-- Read particle data from previous model run.
    3009 !-- First open the input unit.
    3010     IF ( myid_char == '' )  THEN
    3011        OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char,                  &
    3012                   FORM='UNFORMATTED' )
    3013     ELSE
    3014        OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char,                 &
    3015                   FORM='UNFORMATTED' )
    3016     ENDIF
    3017 
    3018 !
    3019 !-- First compare the version numbers
    3020     READ ( 90 )  version_on_file
    3021     particle_binary_version = '4.0'
    3022     IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
    3023        message_string = 'version mismatch concerning data from prior ' //      &
    3024                         'run &version on file = "' //                          &
    3025                                       TRIM( version_on_file ) //               &
    3026                         '&version in program = "' //                           &
    3027                                       TRIM( particle_binary_version ) // '"'
    3028        CALL message( 'lpm_read_restart_file', 'PA0214', 1, 2, 0, 6, 0 )
    3029     ENDIF
    3030 
    3031 !
    3032 !-- If less particles are stored on the restart file than prescribed by
    3033 !-- 1, the remainder is initialized by zero_particle to avoid
    3034 !-- errors.
    3035     zero_particle = particle_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
    3036                                    0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
    3037                                    0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
    3038                                    0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
    3039                                    0, 0, 0_idp, .FALSE., -1 )
    3040 !
    3041 !-- Read some particle parameters and the size of the particle arrays,
    3042 !-- allocate them and read their contents.
    3043     READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                     &
    3044                  last_particle_release_time, number_of_particle_groups,        &
    3045                  particle_groups, time_write_particle_data
    3046 
    3047     ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
    3048               grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    3049 
    3050     READ ( 90 )  prt_count
    3051 
    3052     DO  ip = nxl, nxr
    3053        DO  jp = nys, nyn
    3054           DO  kp = nzb+1, nzt
    3055 
    3056              number_of_particles = prt_count(kp,jp,ip)
    3057              IF ( number_of_particles > 0 )  THEN
    3058                 alloc_size = MAX( INT( number_of_particles *                   &
    3059                              ( 1.0_wp + alloc_factor / 100.0_wp ) ),           &
    3060                              1 )
    3061              ELSE
    3062                 alloc_size = 1
    3063              ENDIF
    3064 
    3065              ALLOCATE( grid_particles(kp,jp,ip)%particles(1:alloc_size) )
    3066 
    3067              IF ( number_of_particles > 0 )  THEN
    3068                 ALLOCATE( tmp_particles(1:number_of_particles) )
    3069                 READ ( 90 )  tmp_particles
    3070                 grid_particles(kp,jp,ip)%particles(1:number_of_particles) = tmp_particles
    3071                 DEALLOCATE( tmp_particles )
    3072                 IF ( number_of_particles < alloc_size )  THEN
    3073                    grid_particles(kp,jp,ip)%particles(number_of_particles+1:alloc_size) &
    3074                       = zero_particle
     3041    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
     3042
     3043!
     3044!--    Read particle data from previous model run.
     3045!--    First open the input unit.
     3046       IF ( myid_char == '' )  THEN
     3047          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char,                  &
     3048                     FORM='UNFORMATTED' )
     3049       ELSE
     3050          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char,                 &
     3051                     FORM='UNFORMATTED' )
     3052       ENDIF
     3053
     3054!
     3055!--    First compare the version numbers
     3056       READ ( 90 )  version_on_file
     3057       particle_binary_version = '4.0'
     3058       IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
     3059          message_string = 'version mismatch concerning data from prior ' //      &
     3060                           'run &version on file = "' //                          &
     3061                                         TRIM( version_on_file ) //               &
     3062                           '&version in program = "' //                           &
     3063                                         TRIM( particle_binary_version ) // '"'
     3064          CALL message( 'lpm_read_restart_file', 'PA0214', 1, 2, 0, 6, 0 )
     3065       ENDIF
     3066
     3067!
     3068!--    If less particles are stored on the restart file than prescribed by
     3069!--    1, the remainder is initialized by zero_particle to avoid
     3070!--    errors.
     3071       zero_particle = particle_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
     3072                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
     3073                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
     3074                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
     3075                                      0, 0, 0_idp, .FALSE., -1, -1 )
     3076!
     3077!--    Read some particle parameters and the size of the particle arrays,
     3078!--    allocate them and read their contents.
     3079       READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                     &
     3080                    last_particle_release_time, number_of_particle_groups,        &
     3081                    particle_groups, time_write_particle_data
     3082
     3083       ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
     3084                 grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3085
     3086       READ ( 90 )  prt_count
     3087
     3088       DO  ip = nxl, nxr
     3089          DO  jp = nys, nyn
     3090             DO  kp = nzb+1, nzt
     3091
     3092                number_of_particles = prt_count(kp,jp,ip)
     3093                IF ( number_of_particles > 0 )  THEN
     3094                   alloc_size = MAX( INT( number_of_particles *                   &
     3095                                ( 1.0_wp + alloc_factor / 100.0_wp ) ),           &
     3096                                1 )
     3097                ELSE
     3098                   alloc_size = 1
    30753099                ENDIF
    3076              ELSE
    3077                 grid_particles(kp,jp,ip)%particles(1:alloc_size) = zero_particle
    3078              ENDIF
    3079 
     3100
     3101                ALLOCATE( grid_particles(kp,jp,ip)%particles(1:alloc_size) )
     3102
     3103                IF ( number_of_particles > 0 )  THEN
     3104                   ALLOCATE( tmp_particles(1:number_of_particles) )
     3105                   READ ( 90 )  tmp_particles
     3106                   grid_particles(kp,jp,ip)%particles(1:number_of_particles) = tmp_particles
     3107                   DEALLOCATE( tmp_particles )
     3108                   IF ( number_of_particles < alloc_size )  THEN
     3109                      grid_particles(kp,jp,ip)%particles(number_of_particles+1:alloc_size) &
     3110                         = zero_particle
     3111                   ENDIF
     3112                ELSE
     3113                   grid_particles(kp,jp,ip)%particles(1:alloc_size) = zero_particle
     3114                ENDIF
     3115
     3116             ENDDO
    30803117          ENDDO
    30813118       ENDDO
    3082     ENDDO
    3083 
    3084     CLOSE ( 90 )
     3119
     3120       CLOSE ( 90 )
     3121
     3122    ELSEIF ( restart_data_format_input(1:3) == 'mpi' )  THEN
     3123
     3124       WRITE ( 9, * )  'Here is MPI-IO praticle input ', rd_mpi_io_check_open()
     3125       FLUSH(9)
     3126
     3127       ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
     3128                 grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3129
     3130       ALLOCATE( prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3131!
     3132!--    Open restart file for read, if not already open, and do not allow usage of
     3133!--    shared-memory I/O
     3134       IF ( .NOT. rd_mpi_io_check_open() )  THEN
     3135          save_restart_data_format_input = restart_data_format_input
     3136          restart_data_format_input = 'mpi'
     3137          CALL rd_mpi_io_open( 'READ', 'BININ' )
     3138          restart_data_format_input = save_restart_data_format_input
     3139       ENDIF
     3140
     3141       CALL  rd_mpi_io_particle_filetypes
     3142
     3143       prt_count = 0
     3144       CALL rrd_mpi_io( 'prt_count', prt_count )
     3145       CALL rrd_mpi_io( 'prt_global_index', prt_global_index )
     3146
     3147!
     3148!--    Allocate particles arrays
     3149       DO  ip = nxl, nxr
     3150          DO  jp = nys, nyn
     3151             DO  kp = nzb+1, nzt
     3152
     3153                number_of_particles = prt_count(kp,jp,ip)
     3154                IF ( number_of_particles > 0 )  THEN
     3155                   alloc_size = MAX( INT( number_of_particles *                   &
     3156                      ( 1.0_wp + alloc_factor / 100.0_wp ) ),           &
     3157                      1 )
     3158                ELSE
     3159                   alloc_size = 1
     3160                ENDIF
     3161
     3162                ALLOCATE( grid_particles(kp,jp,ip)%particles(1:alloc_size) )
     3163
     3164             ENDDO
     3165          ENDDO
     3166       ENDDO
     3167
     3168!
     3169!--    Now read particle data from restart file
     3170       CALL rrd_mpi_io_particles( 'particles', prt_global_index )
     3171
     3172       IF ( .NOT. rd_mpi_io_check_open() )  THEN
     3173!
     3174!--       Do not print header a second time to the debug file
     3175          save_debug_output = debug_output
     3176          debug_output      = .FALSE.
     3177          CALL rd_mpi_io_close()
     3178          debug_output = save_debug_output
     3179       ENDIF
     3180
     3181       DEALLOCATE( prt_global_index )
     3182
     3183    ENDIF
    30853184!
    30863185!-- Must be called to sort particles into blocks, which is needed for a fast
    30873186!-- interpolation of the LES fields on the particle position.
    30883187    CALL lpm_sort_and_delete
    3089 
    30903188
    30913189 END SUBROUTINE lpm_rrd_local_particles
     
    32563354 
    32573355    CHARACTER (LEN=10) ::  particle_binary_version   !<
    3258     CHARACTER (LEN=20) ::  tmp_name                  !< temporary variable
     3356    CHARACTER (LEN=32) ::  tmp_name                  !< temporary variable
    32593357
    32603358    INTEGER(iwp) ::  i                               !< loop index
    32613359    INTEGER(iwp) ::  ip                              !<
     3360    INTEGER(iwp) ::  j                               !< loop index
    32623361    INTEGER(iwp) ::  jp                              !<
     3362    INTEGER(iwp) ::  k                               !< loop index
    32633363    INTEGER(iwp) ::  kp                              !<
    3264 !
    3265 !-- First open the output unit.
    3266     IF ( myid_char == '' )  THEN
    3267        OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT'//myid_char, &
    3268                   FORM='UNFORMATTED')
    3269     ELSE
    3270        IF ( myid == 0 )  CALL local_system( 'mkdir PARTICLE_RESTART_DATA_OUT' )
     3364
    32713365#if defined( __parallel )
    3272 !
    3273 !--    Set a barrier in order to allow that thereafter all other processors
    3274 !--    in the directory created by PE0 can open their file
    3275        CALL MPI_BARRIER( comm2d, ierr )
     3366    INTEGER      :: ierr                             !<
    32763367#endif
    3277        OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT/'//myid_char, &
    3278                   FORM='UNFORMATTED' )
    3279     ENDIF
    3280 
    3281 !
    3282 !-- Write the version number of the binary format.
    3283 !-- Attention: After changes to the following output commands the version
    3284 !-- ---------  number of the variable particle_binary_version must be
    3285 !--            changed! Also, the version number and the list of arrays
    3286 !--            to be read in lpm_read_restart_file must be adjusted
    3287 !--            accordingly.
    3288     particle_binary_version = '4.0'
    3289     WRITE ( 90 )  particle_binary_version
    3290 
    3291 !
    3292 !-- Write some particle parameters, the size of the particle arrays
    3293     WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                    &
    3294                   last_particle_release_time, number_of_particle_groups,       &
    3295                   particle_groups, time_write_particle_data
    3296 
    3297     WRITE ( 90 )  prt_count
     3368    INTEGER(iwp) ::  start_index                     !<
     3369    INTEGER(iwp) ::  start_index_on_pe               !<
     3370
     3371    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  nr_particles_global
     3372    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  nr_particles_local
     3373
     3374    INTEGER(idp), ALLOCATABLE, DIMENSION(:,:,:) ::  prt_global_index
     3375
     3376
     3377    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     3378!
     3379!--    First open the output unit.
     3380       IF ( myid_char == '' )  THEN
     3381          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT'//myid_char, &
     3382                     FORM='UNFORMATTED')
     3383       ELSE
     3384          IF ( myid == 0 )  CALL local_system( 'mkdir PARTICLE_RESTART_DATA_OUT' )
     3385#if defined( __parallel )
     3386!
     3387!--       Set a barrier in order to allow that thereafter all other processors
     3388!--       in the directory created by PE0 can open their file
     3389          CALL MPI_BARRIER( comm2d, ierr )
     3390#endif
     3391          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT/'//myid_char, &
     3392                     FORM='UNFORMATTED' )
     3393       ENDIF
     3394
     3395!
     3396!--    Write the version number of the binary format.
     3397!--    Attention: After changes to the following output commands the version
     3398!--    ---------  number of the variable particle_binary_version must be
     3399!--               changed! Also, the version number and the list of arrays
     3400!--               to be read in lpm_read_restart_file must be adjusted
     3401!--               accordingly.
     3402       particle_binary_version = '4.0'
     3403       WRITE ( 90 )  particle_binary_version
     3404
     3405!
     3406!--    Write some particle parameters, the size of the particle arrays
     3407       WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                    &
     3408                     last_particle_release_time, number_of_particle_groups,       &
     3409                     particle_groups, time_write_particle_data
     3410
     3411       WRITE ( 90 )  prt_count
    32983412         
    3299     DO  ip = nxl, nxr
    3300        DO  jp = nys, nyn
    3301           DO  kp = nzb+1, nzt
    3302              number_of_particles = prt_count(kp,jp,ip)
    3303              particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
    3304              IF ( number_of_particles <= 0 )  CYCLE
    3305              WRITE ( 90 )  particles
     3413       DO  ip = nxl, nxr
     3414          DO  jp = nys, nyn
     3415             DO  kp = nzb+1, nzt
     3416                number_of_particles = prt_count(kp,jp,ip)
     3417                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
     3418                IF ( number_of_particles <= 0 )  CYCLE
     3419                WRITE ( 90 )  particles
     3420             ENDDO
    33063421          ENDDO
    33073422       ENDDO
    3308     ENDDO
    3309 
    3310     CLOSE ( 90 )
     3423
     3424       CLOSE ( 90 )
    33113425
    33123426#if defined( __parallel )
     
    33143428#endif
    33153429
    3316     IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
    33173430
    33183431       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     
    33213434       ENDIF
    33223435
     3436
    33233437    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
     3438
    33243439
    33253440       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     
    33303445       ENDIF
    33313446
     3447       ALLOCATE( prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3448
     3449#if defined( __parallel )
     3450!--    TODO: needs to be replaced by standard PALM message
     3451       IF ( TRIM( restart_data_format_output ) == 'mpi_shared_memory' )   THEN
     3452          WRITE( 9, * )  'mpi_shared_memory is NOT implemented yet for particle IO'
     3453          FLUSH( 9 )
     3454          CALL MPI_ABORT( MPI_COMM_WORLD, 1, ierr )
     3455       ENDIF
     3456#endif
     3457
     3458       CALL rd_mpi_io_particle_filetypes
     3459
     3460       nr_particles_local = 0
     3461       nr_particles_local(myid) = SUM( prt_count )
     3462
     3463#if defined( __parallel )
     3464       CALL MPI_ALLREDUCE( nr_particles_local, nr_particles_global, numprocs, MPI_INTEGER,         &
     3465                           MPI_SUM, comm2d, ierr )
     3466#else
     3467       nr_particles_global = nr_particles_local
     3468#endif
     3469
     3470       start_index_on_pe = 0
     3471       IF ( myid > 0 )  THEN
     3472          DO  i = 1, myid
     3473             start_index_on_pe = start_index_on_pe + nr_particles_global(i-1)
     3474          ENDDO
     3475       ENDIF
     3476
     3477       CALL wrd_mpi_io( 'prt_count', prt_count )
     3478
     3479       start_index = start_index_on_pe
     3480       DO  i = nxl, nxr
     3481          DO  j = nys, nyn
     3482             DO  k = nzb, nzt+1
     3483                prt_global_index(k,j,i) = start_index
     3484                start_index             = start_index + prt_count(k,j,i)
     3485             ENDDO
     3486          ENDDO
     3487       ENDDO
     3488
     3489       CALL wrd_mpi_io( 'prt_global_index', prt_global_index )
     3490       CALL wrd_mpi_io_particles( 'particles', prt_global_index )
     3491
     3492       DEALLOCATE( prt_global_index )
     3493
    33323494    ENDIF
    33333495
     
    33413503!------------------------------------------------------------------------------!
    33423504 SUBROUTINE lpm_wrd_global
     3505
     3506#if defined( __parallel )
     3507    INTEGER :: ierr  !<
     3508#endif
     3509
     3510    REAL(wp), DIMENSION(4,max_number_of_particle_groups) ::  particle_groups_array  !<
     3511
    33433512 
    33443513    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     
    33623531       CALL wrd_mpi_io( 'interpolation_simple_predictor', interpolation_simple_predictor )
    33633532       CALL wrd_mpi_io( 'interpolation_trilinear', interpolation_trilinear )
     3533!
     3534!--    Write some global particle parameters
     3535!--    In case of Fortran binary format, these variables are written to unit 90
     3536       CALL wrd_mpi_io( 'bc_par_b', bc_par_b )
     3537       CALL wrd_mpi_io( 'bc_par_lr', bc_par_lr )
     3538       CALL wrd_mpi_io( 'bc_par_ns', bc_par_ns )
     3539       CALL wrd_mpi_io( 'bc_par_t', bc_par_t )
     3540       CALL wrd_mpi_io( 'last_particle_release_time', last_particle_release_time )
     3541       CALL wrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups )
     3542       CALL wrd_mpi_io( 'time_write_particle_data', time_write_particle_data )
     3543
     3544!
     3545!--    Write particle_group informations via 2D array to avoid another overlay in
     3546!--    restart_data_mpi_io_mod.
     3547!--    TODO: convert the following to a standard PALM message
     3548       IF( STORAGE_SIZE( particle_groups(1) ) / (wp*8) /= 4 )  THEN
     3549          WRITE( 9, * )  'size of structure particle_groups_type has changed '
     3550          FLUSH( 9 )
     3551#if defined( __parallel )
     3552          CALL MPI_ABORT( MPI_COMM_WORLD, 1, ierr )
     3553#else
     3554          STOP 'error'
     3555#endif
     3556       ENDIF
     3557
     3558       particle_groups_array(1,:) = particle_groups(:)%density_ratio
     3559       particle_groups_array(2,:) = particle_groups(:)%radius
     3560       particle_groups_array(3,:) = particle_groups(:)%exp_arg
     3561       particle_groups_array(4,:) = particle_groups(:)%exp_term
     3562
     3563       CALL wrd_mpi_io_global_array( 'particle_groups', particle_groups_array )
    33643564
    33653565    ENDIF
     
    34123612 SUBROUTINE lpm_rrd_global_mpi
    34133613
     3614#if defined( __parallel )
     3615    INTEGER    :: ierr    !<
     3616#endif
     3617
     3618    REAL(wp), DIMENSION(4,max_number_of_particle_groups) ::  particle_groups_array  !<
     3619
     3620
    34143621    CALL rrd_mpi_io( 'curvature_solution_effects', curvature_solution_effects )
    34153622    CALL rrd_mpi_io( 'interpolation_simple_corrector', interpolation_simple_corrector )
    34163623    CALL rrd_mpi_io( 'interpolation_simple_predictor', interpolation_simple_predictor )
    34173624    CALL rrd_mpi_io( 'interpolation_trilinear', interpolation_trilinear )
     3625!
     3626!-- Read some particle parameters.
     3627!-- In case of Fortran binary format, these variables are read from unit 90.
     3628    CALL rrd_mpi_io( 'bc_par_b', bc_par_b )
     3629    CALL rrd_mpi_io( 'bc_par_lr', bc_par_lr )
     3630    CALL rrd_mpi_io( 'bc_par_ns', bc_par_ns )
     3631    CALL rrd_mpi_io( 'bc_par_t', bc_par_t )
     3632    CALL rrd_mpi_io( 'last_particle_release_time', last_particle_release_time )
     3633    CALL rrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups )
     3634    CALL rrd_mpi_io( 'time_write_particle_data', time_write_particle_data )
     3635
     3636!
     3637!-- Read particle group information via 2d-array to avoid another overlay in
     3638!-- restart_data_mpi_io_mod.
     3639!-- TODO: convert the following to a standard PALM message
     3640    IF ( STORAGE_SIZE( particle_groups(1) ) / (wp*8) /= 4 )  THEN
     3641       WRITE( 9, * )  'size of structure particle_groups_type has changed '
     3642       FLUSH( 9 )
     3643#if defined( __parallel )
     3644       CALL MPI_ABORT( MPI_COMM_WORLD, 1, ierr )
     3645#else
     3646       STOP 'error'
     3647#endif
     3648    ENDIF
     3649
     3650    CALL rrd_mpi_io_global_array( 'particle_groups', particle_groups_array )
     3651
     3652    particle_groups(:)%density_ratio = particle_groups_array(1,:)
     3653    particle_groups(:)%radius        = particle_groups_array(2,:)
     3654    particle_groups(:)%exp_arg       = particle_groups_array(3,:)
     3655    particle_groups(:)%exp_term      = particle_groups_array(4,:)
    34183656
    34193657 END SUBROUTINE lpm_rrd_global_mpi
Note: See TracChangeset for help on using the changeset viewer.