Changeset 4546 for palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
- Timestamp:
- May 24, 2020 12:16:41 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
r4545 r4546 25 25 ! ----------------- 26 26 ! $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 27 31 ! Using parallel random generator, thus preventing dependency of PE number 28 32 ! … … 176 180 intermediate_timestep_count, intermediate_timestep_count_max, & 177 181 message_string, molecular_viscosity, ocean_mode, & 178 particle_maximum_age, iran, restart_data_format_output,&182 particle_maximum_age, restart_data_format_output, & 179 183 simulated_time, topography, dopts_time_count, & 180 184 time_since_reference_point, rho_surface, u_gtrans, v_gtrans, & … … 260 264 INTEGER(iwp) :: deleted_particles = 0 !< number of deleted particles per time step 261 265 INTEGER(iwp) :: i_splitting_mode !< dummy for splitting mode 262 INTEGER(iwp) :: iran_part = -1234567 !< number for random generator263 266 INTEGER(iwp) :: max_number_particles_per_gridbox = 100 !< namelist parameter (see documentation) 264 267 INTEGER(iwp) :: isf !< dummy for splitting function … … 282 285 INTEGER(iwp) :: trnp_count_recv_sum !< parameter for particle exchange of PEs 283 286 284 INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE :: seq_random_array_particle !< sequence of random array for particle287 INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE :: seq_random_array_particles !< sequence of random array for particle 285 288 286 289 LOGICAL :: lagrangian_particle_model = .FALSE. !< namelist parameter (see documentation) … … 1249 1252 particle_groups(i)%radius = radius(i) 1250 1253 ENDDO 1251 !1252 !-- Set a seed value for the random number generator to be exclusively1253 !-- used for the particle code. The generated random numbers should be1254 !-- different on the different PEs.1255 iran_part = iran_part + myid1256 1254 1257 1255 ! 1258 1256 !-- Initialize parallel random number sequence seed for particles 1259 !-- This is done individually, as thus particle random numbers does1260 !-- n ot affect random numbers used for the flow field.1261 ALLOCATE ( seq_random_array_particle (5,nys:nyn,nxl:nxr) )1262 seq_random_array_particle = 01257 !-- 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 1263 1261 1264 1262 !-- Initializing with random_seed_parallel for every vertical … … 1269 1267 CALL random_seed_parallel (random_sequence=id_random_array(j, i)) 1270 1268 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)) 1272 1270 ENDDO 1273 1271 ENDDO … … 1537 1535 ! 1538 1536 !-- 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) ) 1540 1538 DO kp = nzb+1, nzt 1541 1539 number_of_particles = prt_count(kp,jp,ip) … … 1607 1605 ENDDO 1608 1606 ! 1609 !-- Get the new random seeds from last call at grid point jp, ip1610 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) ) 1611 1609 ENDDO 1612 1610 ENDDO … … 1738 1736 ! 1739 1737 !-- 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) ) 1741 1739 DO kp = nzb+1, nzt 1742 1740 … … 1771 1769 particles(n)%weight_factor = particles(n)%weight_factor * aero_weight 1772 1770 ! 1773 !-- create random numver with parallel number generator1771 !-- Create random numver with parallel number generator 1774 1772 CALL random_number_parallel( random_dummy ) 1775 1773 IF ( particles(n)%weight_factor - FLOOR(particles(n)%weight_factor,KIND=wp) & … … 1819 1817 ENDDO 1820 1818 ! 1821 !-- Get the new random seeds from last call at grid point j1822 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) ) 1823 1821 ENDDO 1824 1822 ENDDO … … 2215 2213 ! 2216 2214 !-- 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) ) 2218 2216 2219 2217 DO k = nzb+1, nzt … … 2301 2299 ! 2302 2300 !-- 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) ) 2304 2302 2305 2303 ENDDO … … 3110 3108 LOGICAL, INTENT(OUT) :: found 3111 3109 3110 INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE :: tmp_2d_seq_random_particles !< temporary array for storing random generator data for the lpm 3111 3112 3112 REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d !< 3113 3113 … … 3116 3116 3117 3117 SELECT CASE ( restart_string(1:length) ) 3118 3119 CASE ( 'iran' ) ! matching random numbers is still unresolved issue3120 IF ( k == 1 ) READ ( 13 ) iran, iran_part3121 3118 3122 3119 CASE ( 'pc_av' ) … … 3160 3157 tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp) 3161 3158 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 3162 3169 CASE DEFAULT 3163 3170 … … 3178 3185 IMPLICIT NONE 3179 3186 3187 CHARACTER (LEN=20) :: tmp_name !< temporary variable 3188 3189 INTEGER(iwp) :: i !< loop index 3190 3180 3191 LOGICAL :: array_found !< 3181 3182 CALL rrd_mpi_io( 'iran', iran ) ! matching random numbers is still unresolved issue3183 CALL rrd_mpi_io( 'iran_part', iran_part )3184 3192 3185 3193 CALL rd_mpi_io_check_array( 'pc_av' , found = array_found ) … … 3211 3219 IF ( .NOT. ALLOCATED( ql_vp_av ) ) ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 3212 3220 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 3213 3232 ENDIF 3214 3233 … … 3224 3243 3225 3244 CHARACTER (LEN=10) :: particle_binary_version !< 3226 3245 CHARACTER (LEN=20) :: tmp_name !< temporary variable 3246 3247 INTEGER(iwp) :: i !< loop index 3227 3248 INTEGER(iwp) :: ip !< 3228 3249 INTEGER(iwp) :: jp !< … … 3282 3303 IF ( TRIM( restart_data_format_output ) == 'fortran_binary' ) THEN 3283 3304 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 3286 3309 3287 3310 ELSEIF ( restart_data_format_output(1:3) == 'mpi' ) THEN 3288 3311 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 3291 3318 3292 3319 ENDIF
Note: See TracChangeset
for help on using the changeset viewer.