Ignore:
Timestamp:
Apr 11, 2014 5:15:14 PM (10 years ago)
Author:
hoffmann
Message:

new Lagrangian particle structure integrated

File:
1 edited

Legend:

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

    r1321 r1359  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! New particle structure integrated.
    2323!
    2424! Former revisions:
     
    4949        ONLY:  nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz, nzb, nzt
    5050
     51    USE kinds
     52
     53    USE lpm_pack_arrays_mod,                                                   &
     54        ONLY:  lpm_pack_all_arrays
     55
    5156    USE particle_attributes,                                                   &
    52         ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, initial_particles,    &
    53                number_of_initial_particles, maximum_number_of_particles,       &
     57        ONLY:  alloc_factor, bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,         &
     58               grid_particles, maximum_number_of_particles,                    &
    5459               maximum_number_of_tailpoints, maximum_number_of_tails,          &
    55                new_tail_id, number_of_particles, number_of_particle_groups,    &
    56                number_of_tails, particles, particle_groups, particle_mask,     &
    57                particle_tail_coordinates, particle_type, part_1, part_2,       &
    58                prt_count, prt_start_index,  sort_count, tail_mask, time_prel,  &
    59                time_write_particle_data, uniform_particles, use_particle_tails
    60 
     60               min_nr_particle, new_tail_id, number_of_particles,              &
     61               number_of_particle_groups, number_of_tails, particles,          &
     62               particle_groups, particle_tail_coordinates, particle_type,      &
     63               prt_count, sort_count, tail_mask, time_prel,                    &
     64               time_write_particle_data, uniform_particles,                    &
     65               use_particle_tails, zero_particle
    6166
    6267    USE pegrid
     
    6671    CHARACTER (LEN=10) ::  particle_binary_version    !:
    6772    CHARACTER (LEN=10) ::  version_on_file            !:
     73
     74    INTEGER(iwp) :: alloc_size !:
     75    INTEGER(iwp) :: ip         !:
     76    INTEGER(iwp) :: jp         !:
     77    INTEGER(iwp) :: kp         !:
     78
     79    TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: tmp_particles !:
    6880
    6981!
     
    8193!-- First compare the version numbers
    8294    READ ( 90 )  version_on_file
    83     particle_binary_version = '3.0'
     95    particle_binary_version = '3.2'
    8496    IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
    8597       message_string = 'version mismatch concerning data from prior ' // &
     
    92104
    93105!
     106!-- If less particles are stored on the restart file than prescribed by
     107!-- min_nr_particle, the remainder is initialized by zero_particle to avoid
     108!-- errors.
     109#if defined( __twocachelines )
     110    zero_particle = particle_type( 0.0_wp, 0.0_sp, 0.0_sp, 0.0_sp, 0.0_sp,  &
     111                                   0.0_sp, 0.0_sp, 0.0_wp, 0.0_wp, 0.0_wp,  &
     112                                   0, .FALSE., 0.0_wp, 0.0_wp, 0.0_wp,      &
     113                                   0.0_sp, 0.0_sp, 0.0_sp, 0.0_sp, 0.0_sp,  &
     114                                   0.0_sp, 0, 0, 0, -1)
     115#else
     116    zero_particle = particle_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
     117                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
     118                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
     119                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0, 0, 0, &
     120                                   0, .FALSE., -1)
     121#endif
     122
     123!
    94124!-- Read some particle parameters and the size of the particle arrays,
    95125!-- allocate them and read their contents.
    96126    READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                  &
    97                  maximum_number_of_particles, maximum_number_of_tailpoints, &
    98                  maximum_number_of_tails, number_of_initial_particles,      &
    99                  number_of_particles, number_of_particle_groups,            &
    100                  number_of_tails, particle_groups, time_prel,               &
    101                  time_write_particle_data, uniform_particles
     127                 maximum_number_of_tailpoints, maximum_number_of_tails,     &
     128                 number_of_particle_groups, number_of_tails,                &
     129                 particle_groups, time_prel, time_write_particle_data,      &
     130                 uniform_particles
    102131
    103     IF ( number_of_initial_particles /= 0 )  THEN
    104        ALLOCATE( initial_particles(1:number_of_initial_particles) )
    105        READ ( 90 )  initial_particles
    106     ENDIF
     132    ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                     &
     133              grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    107134
    108     ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
    109               prt_start_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
    110               particle_mask(maximum_number_of_particles),     &
    111               part_1(maximum_number_of_particles),            &
    112               part_2(maximum_number_of_particles) )
     135    READ ( 90 )  prt_count
    113136
    114     part_1 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    115                             0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    116                             0.0, 0, 0, 0, 0 )
     137    maximum_number_of_particles = 0
     138    DO  ip = nxl, nxr
     139       DO  jp = nys, nyn
     140          DO  kp = nzb+1, nzt
    117141
    118     part_2 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    119                             0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    120                             0.0, 0, 0, 0, 0 )
     142             number_of_particles = prt_count(kp,jp,ip)
     143             IF ( number_of_particles > 0 )  THEN
     144                alloc_size = MAX( INT( number_of_particles *                   &
     145                             ( 1.0_wp + alloc_factor / 100.0_wp ) ),           &
     146                             min_nr_particle )
     147             ELSE
     148                alloc_size = min_nr_particle
     149             ENDIF
    121150
    122     sort_count = 0
     151             ALLOCATE( grid_particles(kp,jp,ip)%particles(1:alloc_size) )
    123152
    124     particles => part_1
     153             IF ( number_of_particles > 0 )  THEN
     154                ALLOCATE( tmp_particles(1:number_of_particles) )
     155                READ ( 90 )  tmp_particles
     156                grid_particles(kp,jp,ip)%particles(1:number_of_particles) = tmp_particles
     157                DEALLOCATE( tmp_particles )
     158                IF ( number_of_particles < alloc_size )  THEN
     159                   grid_particles(kp,jp,ip)%particles(number_of_particles+1:alloc_size) &
     160                      = zero_particle
     161                ENDIF
     162             ELSE
     163                grid_particles(kp,jp,ip)%particles(1:alloc_size) = zero_particle
     164             ENDIF
    125165
    126     READ ( 90 )  prt_count, prt_start_index
    127     READ ( 90 )  particles
     166             maximum_number_of_particles = maximum_number_of_particles + alloc_size
    128167
    129     IF ( use_particle_tails )  THEN
    130        ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
    131                  maximum_number_of_tails),                                 &
    132                  new_tail_id(maximum_number_of_tails),                     &
    133                  tail_mask(maximum_number_of_tails) )
    134        READ ( 90 )  particle_tail_coordinates
    135     ENDIF
     168          ENDDO
     169       ENDDO
     170    ENDDO
     171
     172!
     173!-- particle tails currently not available
     174!    IF ( use_particle_tails )  THEN
     175!       ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
     176!                 maximum_number_of_tails),                                 &
     177!                 new_tail_id(maximum_number_of_tails),                     &
     178!                 tail_mask(maximum_number_of_tails) )
     179!       READ ( 90 )  particle_tail_coordinates
     180!    ENDIF
    136181
    137182    CLOSE ( 90 )
     183!
     184!-- Must be called to sort particles into blocks, which is needed for a fast
     185!-- interpolation of the LES fields on the particle position.
     186    CALL lpm_pack_all_arrays
    138187
    139188
Note: See TracChangeset for help on using the changeset viewer.