Ignore:
Timestamp:
May 24, 2020 12:16:41 PM (4 years ago)
Author:
raasch
Message:

Variables iran and iran_part completely removed, added I/O of parallel random numbers to restart file, file re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4545 r4546  
    2525! -----------------
    2626! $Id$
     27! Variables iran and iran_part completely removed, added I/O of parallel random numbers to restart
     28! file
     29!
     30! 4545 2020-05-22 13:17:57Z schwenkel
    2731! Using parallel random generator, thus preventing dependency of PE number
    2832!
     
    176180               intermediate_timestep_count, intermediate_timestep_count_max,   &
    177181               message_string, molecular_viscosity, ocean_mode,                &
    178                particle_maximum_age, iran, restart_data_format_output,         &
     182               particle_maximum_age, restart_data_format_output,               &
    179183               simulated_time, topography, dopts_time_count,                   &
    180184               time_since_reference_point, rho_surface, u_gtrans, v_gtrans,    &
     
    260264    INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step   
    261265    INTEGER(iwp) ::  i_splitting_mode                             !< dummy for splitting mode
    262     INTEGER(iwp) ::  iran_part = -1234567                         !< number for random generator   
    263266    INTEGER(iwp) ::  max_number_particles_per_gridbox = 100       !< namelist parameter (see documentation)
    264267    INTEGER(iwp) ::  isf                                          !< dummy for splitting function
     
    282285    INTEGER(iwp) ::  trnp_count_recv_sum                          !< parameter for particle exchange of PEs
    283286
    284     INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  seq_random_array_particle   !< sequence of random array for particle
     287    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  seq_random_array_particles   !< sequence of random array for particle
    285288
    286289    LOGICAL ::  lagrangian_particle_model = .FALSE.       !< namelist parameter (see documentation)
     
    12491252          particle_groups(i)%radius        = radius(i)
    12501253       ENDDO
    1251 !
    1252 !--    Set a seed value for the random number generator to be exclusively
    1253 !--    used for the particle code. The generated random numbers should be
    1254 !--    different on the different PEs.
    1255        iran_part = iran_part + myid
    12561254
    12571255!
    12581256!--    Initialize parallel random number sequence seed for particles
    1259 !--    This is done individually, as thus particle random numbers does
    1260 !--    not affect random numbers used for the flow field.
    1261        ALLOCATE ( seq_random_array_particle(5,nys:nyn,nxl:nxr) )
    1262        seq_random_array_particle = 0
     1257!--    This is done separately here, as thus particle random numbers do not affect the random
     1258!--    numbers used for the flow field (e.g. for generating flow disturbances).
     1259       ALLOCATE ( seq_random_array_particles(5,nys:nyn,nxl:nxr) )
     1260       seq_random_array_particles = 0
    12631261
    12641262!--    Initializing with random_seed_parallel for every vertical
     
    12691267             CALL random_seed_parallel (random_sequence=id_random_array(j, i))
    12701268             CALL random_number_parallel (random_dummy)
    1271              CALL random_seed_parallel (get=seq_random_array_particle(:, j, i))
     1269             CALL random_seed_parallel (get=seq_random_array_particles(:, j, i))
    12721270          ENDDO
    12731271       ENDDO
     
    15371535!
    15381536!--          Put the random seeds at grid point jp, ip
    1539              CALL random_seed_parallel( put=seq_random_array_particle(:,jp,ip) )
     1537             CALL random_seed_parallel( put=seq_random_array_particles(:,jp,ip) )
    15401538             DO  kp = nzb+1, nzt
    15411539                number_of_particles = prt_count(kp,jp,ip)
     
    16071605             ENDDO
    16081606!
    1609 !--       Get the new random seeds from last call at grid point jp, ip
    1610           CALL random_seed_parallel( get=seq_random_array_particle(:,jp,ip) )
     1607!--          Get the new random seeds from last call at grid point jp, ip
     1608             CALL random_seed_parallel( get=seq_random_array_particles(:,jp,ip) )
    16111609          ENDDO
    16121610       ENDDO
     
    17381736!
    17391737!--       Put the random seeds at grid point jp, ip
    1740           CALL random_seed_parallel( put=seq_random_array_particle(:,jp,ip) )
     1738          CALL random_seed_parallel( put=seq_random_array_particles(:,jp,ip) )
    17411739          DO  kp = nzb+1, nzt
    17421740
     
    17711769                particles(n)%weight_factor = particles(n)%weight_factor * aero_weight
    17721770!
    1773 !--             create random numver with parallel number generator
     1771!--             Create random numver with parallel number generator
    17741772                CALL random_number_parallel( random_dummy )
    17751773                IF ( particles(n)%weight_factor - FLOOR(particles(n)%weight_factor,KIND=wp) &
     
    18191817          ENDDO
    18201818!
    1821 !--    Get the new random seeds from last call at grid point j
    1822        CALL random_seed_parallel( get=seq_random_array_particle(:,jp,ip) )
     1819!--       Get the new random seeds from last call at grid point j
     1820          CALL random_seed_parallel( get=seq_random_array_particles(:,jp,ip) )
    18231821       ENDDO
    18241822    ENDDO
     
    22152213!
    22162214!--                   Put the random seeds at grid point j, i
    2217                       CALL random_seed_parallel( put=seq_random_array_particle(:,j,i) )
     2215                      CALL random_seed_parallel( put=seq_random_array_particles(:,j,i) )
    22182216
    22192217                      DO  k = nzb+1, nzt
     
    23012299!
    23022300!--                   Get the new random seeds from last call at grid point jp, ip
    2303                       CALL random_seed_parallel( get=seq_random_array_particle(:,j,i) )
     2301                      CALL random_seed_parallel( get=seq_random_array_particles(:,j,i) )
    23042302
    23052303                   ENDDO
     
    31103108    LOGICAL, INTENT(OUT)  ::  found
    31113109
     3110    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_2d_seq_random_particles  !< temporary array for storing random generator data for the lpm
     3111
    31123112    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::  tmp_3d   !<
    31133113
     
    31163116
    31173117    SELECT CASE ( restart_string(1:length) )
    3118 
    3119        CASE ( 'iran' ) ! matching random numbers is still unresolved issue
    3120           IF ( k == 1 )  READ ( 13 )  iran, iran_part
    31213118
    31223119        CASE ( 'pc_av' )
     
    31603157               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    31613158
     3159         CASE ( 'seq_random_array_particles' )
     3160             ALLOCATE( tmp_2d_seq_random_particles(5,nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) )
     3161             IF ( .NOT. ALLOCATED( seq_random_array_particles ) )  THEN
     3162                ALLOCATE( seq_random_array_particles(5,nys:nyn,nxl:nxr) )
     3163             ENDIF
     3164             IF ( k == 1 )  READ ( 13 )  tmp_2d_seq_random_particles
     3165             seq_random_array_particles(:,nysc:nync,nxlc:nxrc) =                                   &
     3166                                                  tmp_2d_seq_random_particles(:,nysf:nynf,nxlf:nxrf)
     3167             DEALLOCATE( tmp_2d_seq_random_particles )
     3168
    31623169          CASE DEFAULT
    31633170
     
    31783185    IMPLICIT NONE
    31793186
     3187    CHARACTER (LEN=20) ::  tmp_name  !< temporary variable
     3188
     3189    INTEGER(iwp) ::  i  !< loop index
     3190
    31803191    LOGICAL ::  array_found  !<
    3181 
    3182     CALL rrd_mpi_io( 'iran', iran ) ! matching random numbers is still unresolved issue
    3183     CALL rrd_mpi_io( 'iran_part', iran_part )
    31843192
    31853193    CALL rd_mpi_io_check_array( 'pc_av' , found = array_found )
     
    32113219       IF ( .NOT. ALLOCATED( ql_vp_av ) )  ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    32123220       CALL rrd_mpi_io( 'ql_vp_av', ql_vp_av )
     3221    ENDIF
     3222
     3223    CALL rd_mpi_io_check_array( 'seq_random_array_particles' , found = array_found )
     3224    IF ( array_found )  THEN
     3225       IF ( .NOT. ALLOCATED( seq_random_array_particles ) )  THEN
     3226          ALLOCATE( seq_random_array_particles(5,nys:nyn,nxl:nxr) )
     3227       ENDIF
     3228       DO  i = 1, SIZE( seq_random_array_particles, 1 )
     3229          WRITE( tmp_name, '(A,I2.2)' )  'seq_random_array_particles', i
     3230          CALL rrd_mpi_io( TRIM(tmp_name), seq_random_array_particles(i,:,:) )
     3231       ENDDO
    32133232    ENDIF
    32143233
     
    32243243 
    32253244    CHARACTER (LEN=10) ::  particle_binary_version   !<
    3226 
     3245    CHARACTER (LEN=20) ::  tmp_name                  !< temporary variable
     3246
     3247    INTEGER(iwp) ::  i                               !< loop index
    32273248    INTEGER(iwp) ::  ip                              !<
    32283249    INTEGER(iwp) ::  jp                              !<
     
    32823303    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
    32833304
    3284        CALL wrd_write_string( 'iran' )  ! matching random numbers is still unresolved issue
    3285        WRITE ( 14 )  iran, iran_part
     3305       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     3306          CALL wrd_write_string( 'seq_random_array_particles' )
     3307          WRITE ( 14 )  seq_random_array_particles
     3308       ENDIF
    32863309
    32873310    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
    32883311
    3289        CALL wrd_mpi_io( 'iran', iran )  ! matching random numbers is still unresolved issue
    3290        CALL wrd_mpi_io( 'iran_part', iran_part )
     3312       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     3313          DO  i = 1, SIZE( seq_random_array_particles, 1 )
     3314             WRITE( tmp_name, '(A,I2.2)' )  'seq_random_array_particles', i
     3315             CALL wrd_mpi_io( TRIM( tmp_name ), seq_random_array_particles(i,:,:) )
     3316          ENDDO
     3317       ENDIF
    32913318
    32923319    ENDIF
Note: See TracChangeset for help on using the changeset viewer.