Changeset 4778 for palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
- Timestamp:
- Nov 9, 2020 1:40:05 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
r4731 r4778 24 24 ! ----------------- 25 25 ! $Id$ 26 ! output of particle time series added 27 ! 28 ! 4731 2020-10-07 13:25:11Z schwenkel 26 29 ! Move exchange_horiz from time_integration to modules 27 30 ! … … 209 212 USE cpulog, & 210 213 ONLY: cpu_log, log_point, log_point_s 214 215 USE data_output_particle_mod, & 216 ONLY: dop_active, & 217 dop_finalize, & 218 dop_init, & 219 dop_output_tseries, & 220 dop_prt_axis_dimension, & 221 dop_last_active_particle 211 222 212 223 USE indices, & … … 266 277 surf_lsm_h, & 267 278 surf_usm_h 268 269 !-- Next lines are in preparation for the output of particle data270 ! USE data_output_particle_mod, &271 ! ONLY: dop_active, dop_init, dop_output_tseries272 279 273 280 #if defined( __parallel ) … … 326 333 INTEGER(iwp) :: trnp_count_sum !< parameter for particle exchange of PEs 327 334 335 INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE :: id_counter !< number of particles initialized in each grid box 328 336 INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE :: seq_random_array_particles !< sequence of random array for particle 329 337 … … 410 418 PRIVATE 411 419 412 PUBLIC lpm_parin, & 413 lpm_header, & 414 lpm_init_arrays, & 415 lpm_init, & 416 lpm_actions, & 420 PUBLIC lagrangian_particle_model 421 422 PUBLIC lpm_actions, & 423 lpm_check_parameters, & 417 424 lpm_data_output_ptseries, & 418 425 lpm_exchange_horiz_bounds, & 426 lpm_header, & 427 lpm_init, & 419 428 lpm_interaction_droplets_ptq, & 429 lpm_init_arrays, & 430 lpm_last_actions, & 431 lpm_parin, & 432 lpm_rrd_global, & 433 lpm_rrd_local, & 420 434 lpm_rrd_local_particles, & 421 lpm_wrd_local, &422 lpm_rrd_global, &423 435 lpm_wrd_global, & 424 lpm_rrd_local, & 425 lpm_check_parameters 426 427 PUBLIC lagrangian_particle_model 436 lpm_wrd_local 428 437 429 438 INTERFACE lpm_check_parameters … … 533 542 MODULE PROCEDURE dealloc_particles_array 534 543 END INTERFACE dealloc_particles_array 544 545 INTERFACE lpm_last_actions 546 MODULE PROCEDURE lpm_last_actions 547 END INTERFACE lpm_last_actions 535 548 536 549 INTERFACE lpm_sort_and_delete … … 629 642 collision_kernel, & 630 643 curvature_solution_effects, & 644 data_output_pts, & 631 645 deallocate_memory, & 632 646 density_ratio, & … … 651 665 particle_advection_interpolation, & 652 666 particle_maximum_age, & 653 p art_output, &654 p art_inc,&655 p art_percent,&667 pts_id_file, & 668 pts_increment, & 669 pts_percentage, & 656 670 pdx, & 657 671 pdy, & … … 861 875 SUBROUTINE lpm_check_parameters 862 876 877 LOGICAL :: id_file_exists = .FALSE. 878 863 879 ! 864 880 !-- Collision kernels: … … 880 896 881 897 END SELECT 898 882 899 IF ( collision_kernel(6:9) == 'fast' ) use_kernel_tables = .TRUE. 883 900 … … 897 914 message_string = 'nested runs in combination with cloud droplets ' // & 898 915 'is not implemented' 899 916 CALL message( 'lpm_check_parameters', 'PA0687', 1, 2, 0, 6, 0 ) 900 917 ENDIF 901 918 919 IF ( pts_increment > 1 .AND. pts_percentage < 100.0_wp ) THEN 920 message_string = 'pts_increment and pts_percentage cannot be set both ' 921 CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 ) 922 ENDIF 923 924 IF ( pts_increment < 1 ) THEN 925 message_string = 'pts_increment must be > 1' 926 CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 ) 927 ENDIF 928 929 IF ( pts_percentage > 100.0_wp ) THEN 930 message_string = 'pts_percentage must be < 100' 931 CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 ) 932 ENDIF 933 934 INQUIRE( FILE = pts_id_file, EXIST = id_file_exists ) 935 #if defined( __netcdf4_parallel ) 936 ! 937 !-- Check if individual particles timeseries is set 938 IF ( pts_increment > 1 .AND. dt_dopts /= 9999999.9_wp .OR. & 939 pts_percentage < 100.0_wp .AND. dt_dopts /= 9999999.9_wp .OR. & 940 id_file_exists .AND. dt_dopts /= 9999999.9_wp ) & 941 THEN 942 dop_active = .TRUE. 943 ENDIF 944 #endif 902 945 903 946 END SUBROUTINE lpm_check_parameters … … 948 991 INTEGER(iwp) :: j !< 949 992 INTEGER(iwp) :: k !< 993 994 LOGICAL :: read_restart !< 950 995 951 996 REAL(wp) :: div !< … … 1229 1274 !-- For the first model run of a possible job chain initialize the particles, otherwise read the 1230 1275 !-- particle data from restart file. 1276 read_restart = .FALSE. 1231 1277 IF ( TRIM( initializing_actions ) == 'read_restart_data' & 1232 1278 .AND. read_particles_from_restartfile ) THEN 1233 1279 CALL lpm_rrd_local_particles 1280 1281 read_restart = .TRUE. 1234 1282 ELSE 1235 1283 ! 1236 1284 !-- Allocate particle arrays and set attributes of the initial set of particles, which can be 1237 1285 !-- also periodically released at later times. 1238 ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 1239 grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr) ) 1286 ALLOCATE( grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr), & 1287 id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 1288 prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 1240 1289 1241 1290 number_of_particles = 0 … … 1243 1292 ! 1244 1293 !-- Initialize counter for particle IDs 1245 grid_particles%id_counter = 11294 id_counter = 1 1246 1295 ! 1247 1296 !-- Initialize all particles with dummy values (otherwise errors may occur within restart runs). … … 1314 1363 1315 1364 ! 1316 !-- next line is in preparation for particle data output 1317 ! CALL dop_init 1365 !-- Output of particle time series 1366 IF ( dop_active ) THEN 1367 CALL dop_init( read_restart ) 1368 ENDIF 1318 1369 1319 1370 ! … … 1520 1571 prt_count = local_count 1521 1572 ! 1522 !-- Calculate particle IDs 1573 !-- Calculate particle IDs (for new particles only) 1523 1574 DO ip = nxl, nxr 1524 1575 DO jp = nys, nyn … … 1527 1578 IF ( number_of_particles <= 0 ) CYCLE 1528 1579 particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles) 1529 1530 DO n = local_start(kp,jp,ip), number_of_particles !only new particles 1531 1532 particles(n)%id = 10000_idp**3 * grid_particles(kp,jp,ip)%id_counter + & 1533 10000_idp**2 * kp + 10000_idp * jp + ip 1580 DO n = local_start(kp,jp,ip), number_of_particles 1581 1582 particles(n)%id = 10000_idp**3 * id_counter(kp,jp,ip) + 10000_idp**2 * kp + & 1583 10000_idp * jp + ip 1534 1584 ! 1535 1585 !-- Count the number of particles that have been released before 1536 grid_particles(kp,jp,ip)%id_counter = grid_particles(kp,jp,ip)%id_counter+ 11586 id_counter(kp,jp,ip) = id_counter(kp,jp,ip) + 1 1537 1587 1538 1588 ENDDO 1539 1540 1589 ENDDO 1541 1590 ENDDO … … 2682 2731 CALL cpu_log( log_point(36), 'data_output_ptseries', 'start' ) 2683 2732 2733 IF ( dop_active ) THEN 2734 CALL dop_output_tseries 2735 ENDIF 2736 2684 2737 IF ( myid == 0 ) THEN 2685 2738 ! … … 3052 3105 FLUSH(9) 3053 3106 3054 ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 3055 grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 3056 3057 ALLOCATE( prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 3107 ALLOCATE( grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 3108 id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 3109 prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 3110 prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 3111 3058 3112 ! 3059 3113 !-- Open restart file for read, if not already open, and do not allow usage of shared-memory I/O … … 3068 3122 3069 3123 prt_count = 0 3124 CALL rrd_mpi_io( 'id_counter', id_counter ) 3070 3125 CALL rrd_mpi_io( 'prt_count', prt_count ) 3071 3126 CALL rrd_mpi_io( 'prt_global_index', prt_global_index ) … … 3147 3202 LOGICAL, INTENT(OUT) :: found 3148 3203 3149 REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d !<3150 3204 REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d !< 3205 INTEGER(iwp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d_int !< 3151 3206 3152 3207 found = .TRUE. 3153 3208 3154 3209 SELECT CASE ( restart_string(1:length) ) 3210 3211 CASE ( 'id_counter' ) 3212 IF ( .NOT. ALLOCATED( id_counter ) ) THEN 3213 ALLOCATE( id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 3214 ENDIF 3215 IF ( k == 1 ) READ ( 13 ) tmp_3d_int 3216 id_counter(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = & 3217 tmp_3d_int(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp) 3155 3218 3156 3219 CASE ( 'pc_av' ) … … 3349 3412 #endif 3350 3413 3414 IF ( ALLOCATED( id_counter ) ) THEN 3415 CALL wrd_write_string( 'id_counter' ) 3416 WRITE ( 14 ) id_counter 3417 ENDIF 3351 3418 3352 3419 IF ( ALLOCATED( seq_random_array_particles ) ) THEN … … 3355 3422 ENDIF 3356 3423 3357 3358 3424 ELSEIF ( restart_data_format_output(1:3) == 'mpi' ) THEN 3359 3360 3425 3361 3426 IF ( ALLOCATED( seq_random_array_particles ) ) THEN … … 3396 3461 ENDIF 3397 3462 3398 CALL wrd_mpi_io( 'prt_count', prt_count ) 3463 CALL wrd_mpi_io( 'id_counter', id_counter ) 3464 CALL wrd_mpi_io( 'prt_count', prt_count ) 3399 3465 3400 3466 start_index = start_index_on_pe … … 3437 3503 WRITE ( 14 ) curvature_solution_effects 3438 3504 3505 CALL wrd_write_string( 'dop_last_active_particle' ) 3506 WRITE ( 14 ) dop_last_active_particle 3507 3508 CALL wrd_write_string( 'dop_prt_axis_dimension' ) 3509 WRITE ( 14 ) dop_prt_axis_dimension 3510 3439 3511 CALL wrd_write_string( 'interpolation_simple_corrector' ) 3440 3512 WRITE ( 14 ) interpolation_simple_corrector … … 3459 3531 CALL wrd_mpi_io( 'bc_par_ns', bc_par_ns ) 3460 3532 CALL wrd_mpi_io( 'bc_par_t', bc_par_t ) 3533 CALL wrd_mpi_io( 'dop_last_active_particle', dop_last_active_particle ) 3534 CALL wrd_mpi_io( 'dop_prt_axis_dimension', dop_prt_axis_dimension ) 3461 3535 CALL wrd_mpi_io( 'last_particle_release_time', last_particle_release_time ) 3462 3536 CALL wrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups ) … … 3508 3582 READ ( 13 ) curvature_solution_effects 3509 3583 3584 CASE ( 'dop_last_active_particle' ) 3585 READ ( 13 ) dop_last_active_particle 3586 3587 CASE ( 'dop_prt_axis_dimension' ) 3588 READ ( 13 ) dop_prt_axis_dimension 3589 3510 3590 CASE ( 'interpolation_simple_corrector' ) 3511 3591 READ ( 13 ) interpolation_simple_corrector … … 3551 3631 CALL rrd_mpi_io( 'bc_par_ns', bc_par_ns ) 3552 3632 CALL rrd_mpi_io( 'bc_par_t', bc_par_t ) 3633 CALL rrd_mpi_io( 'dop_prt_axis_dimension', dop_prt_axis_dimension ) 3634 CALL rrd_mpi_io( 'dop_last_active_particle', dop_last_active_particle ) 3553 3635 CALL rrd_mpi_io( 'last_particle_release_time', last_particle_release_time ) 3554 3636 CALL rrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups ) … … 3577 3659 3578 3660 END SUBROUTINE lpm_rrd_global_mpi 3661 3662 3663 !------------------------------------------------------------------------------! 3664 ! Description: 3665 ! ------------ 3666 !> Last actions before PALM finishes. 3667 !------------------------------------------------------------------------------! 3668 SUBROUTINE lpm_last_actions 3669 3670 ! 3671 !-- Close NETCDF file for individual particle timeseries 3672 IF ( dop_active ) THEN 3673 CALL dop_finalize 3674 ENDIF 3675 3676 END SUBROUTINE lpm_last_actions 3579 3677 3580 3678
Note: See TracChangeset
for help on using the changeset viewer.