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.f90

    r1321 r1359  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! New particle structure integrated.
     23! Kind definition added to all floating point numbers.
    2324!
    2425! Former revisions:
     
    8283    USE control_parameters,                                                    &
    8384        ONLY:  cloud_droplets, dt_3d, dt_3d_reached, dt_3d_reached_l,          &
    84                molecular_viscosity, simulated_time
     85               molecular_viscosity, simulated_time, topography
    8586
    8687    USE cpulog,                                                                &
    8788        ONLY:  cpu_log, log_point, log_point_s
    8889
     90    USE indices,                                                               &
     91        ONLY: nxl, nxr, nys, nyn, nzb, nzt
     92
    8993    USE kinds
    9094
     95    USE lpm_exchange_horiz_mod,                                                &
     96        ONLY:  lpm_exchange_horiz, lpm_move_particle
     97
     98    USE lpm_pack_arrays_mod,                                                   &
     99        ONLY:  lpm_pack_all_arrays
     100
    91101    USE particle_attributes,                                                   &
    92         ONLY:  collision_kernel, deleted_particles, dt_sort_particles,         &
    93                deleted_tails, dt_write_particle_data, dt_prel, end_time_prel,  &
    94                number_of_particles, number_of_particle_groups,particles,      &
    95                particle_groups, particle_mask, trlp_count_sum, tail_mask,      &
    96                time_prel, time_sort_particles, time_write_particle_data,       &
    97                trlp_count_recv_sum, trnp_count_sum, trnp_count_recv_sum,       &
    98                trrp_count_sum, trrp_count_recv_sum, trsp_count_sum,            &
    99                trsp_count_recv_sum, use_particle_tails, use_sgs_for_particles, &
    100                write_particle_statistics
     102        ONLY:  collision_kernel, deleted_particles, deleted_tails,             &
     103               dt_write_particle_data, dt_prel, end_time_prel,                 &
     104               grid_particles, number_of_particles, number_of_particle_groups, &
     105               particles, particle_groups, prt_count, trlp_count_sum,          &
     106               tail_mask, time_prel, time_sort_particles,                      &
     107               time_write_particle_data, trlp_count_recv_sum, trnp_count_sum,  &
     108               trnp_count_recv_sum, trrp_count_sum, trrp_count_recv_sum,       &
     109               trsp_count_sum, trsp_count_recv_sum, use_particle_tails,        &
     110               use_sgs_for_particles, write_particle_statistics
    101111
    102112    USE pegrid
     
    104114    IMPLICIT NONE
    105115
    106     INTEGER(iwp) ::  m                       !:
    107 
     116    INTEGER(iwp)       ::  i                  !:
     117    INTEGER(iwp)       ::  ie                 !:
     118    INTEGER(iwp)       ::  is                 !:
     119    INTEGER(iwp)       ::  j                  !:
     120    INTEGER(iwp)       ::  je                 !:
     121    INTEGER(iwp)       ::  js                 !:
     122    INTEGER(iwp)       ::  k                  !:
     123    INTEGER(iwp)       ::  ke                 !:
     124    INTEGER(iwp)       ::  ks                 !:
     125    INTEGER(iwp)       ::  m                  !:
     126    INTEGER(iwp), SAVE ::  steps = 0          !:
     127
     128    LOGICAL            ::  first_loop_stride  !:
    108129
    109130    CALL cpu_log( log_point(25), 'lpm', 'start' )
     
    125146    ENDIF
    126147
    127 
    128148!
    129149!-- Initialize arrays for marking those particles/tails to be deleted after the
    130150!-- (sub-) timestep
    131     particle_mask     = .TRUE.
    132151    deleted_particles = 0
    133152
     
    157176!-- of the particle groups
    158177    DO  m = 1, number_of_particle_groups
    159        IF ( particle_groups(m)%density_ratio /= 0.0 )  THEN
     178       IF ( particle_groups(m)%density_ratio /= 0.0_wp )  THEN
    160179          particle_groups(m)%exp_arg  =                                        &
    161                     4.5 * particle_groups(m)%density_ratio *                   &
     180                    4.5_wp * particle_groups(m)%density_ratio *                &
    162181                    molecular_viscosity / ( particle_groups(m)%radius )**2
    163           particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg * &
    164                                              dt_3d )
     182
     183          particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg *     &
     184                    dt_3d )
    165185       ENDIF
    166186    ENDDO
    167187
    168 
    169 !
    170 !-- Particle (droplet) growth by condensation/evaporation and collision
    171     IF ( cloud_droplets )  THEN
    172 
    173 !
    174 !--    Reset summation arrays
    175        ql_c = 0.0;  ql_v = 0.0;  ql_vp = 0.0
    176 
    177 !
    178 !--    Droplet growth by condensation / evaporation
    179        CALL lpm_droplet_condensation
    180 
    181 !
    182 !--    Particle growth by collision
    183        IF ( collision_kernel /= 'none' )  CALL lpm_droplet_collision
    184 
    185     ENDIF
    186 
    187 
    188 !
    189 !-- If particle advection includes SGS velocity components, calculate the
    190 !-- required SGS quantities (i.e. gradients of the TKE, as well as horizontally
    191 !-- averaged profiles of the SGS TKE and the resolved-scale velocity variances)
    192     IF ( use_sgs_for_particles )  CALL lpm_init_sgs_tke
    193 
    194 
    195 !
    196 !-- Initialize the variable storing the total time that a particle has advanced
    197 !-- within the timestep procedure
    198     particles(1:number_of_particles)%dt_sum = 0.0
    199 
    200 
     188!
     189!-- If necessary, release new set of particles
     190    IF ( time_prel >= dt_prel  .AND.  end_time_prel > simulated_time )  THEN
     191
     192       CALL lpm_release_set
     193!
     194!--    The MOD function allows for changes in the output interval with
     195!--    restart runs.
     196       time_prel = MOD( time_prel, MAX( dt_prel, dt_3d ) )
     197
     198    ENDIF
     199!
     200!-- Reset summation arrays
     201    IF ( cloud_droplets)  THEN
     202       ql_c  = 0.0_wp
     203       ql_v  = 0.0_wp
     204       ql_vp = 0.0_wp
     205    ENDIF
     206
     207    first_loop_stride = .TRUE.
     208    grid_particles(:,:,:)%time_loop_done = .TRUE.
    201209!
    202210!-- Timestep loop for particle advection.
     
    204212!-- (within the total domain!) has reached the LES timestep (dt_3d).
    205213!-- In case of including the SGS velocities, the particle timestep may be
    206 !-- smaller than the LES timestep (because of the Lagrangian timescale restric-
    207 !-- tion) and particles may require to undergo several particle timesteps,
    208 !-- before the LES timestep is reached. Because the number of these particle
    209 !-- timesteps to be carried out is unknown at first, these steps are carried
    210 !-- out in the following infinite loop with exit condition.
     214!-- smaller than the LES timestep (because of the Lagrangian timescale
     215!-- restriction) and particles may require to undergo several particle
     216!-- timesteps, before the LES timestep is reached. Because the number of these
     217!-- particle timesteps to be carried out is unknown at first, these steps are
     218!-- carried out in the following infinite loop with exit condition.
    211219    DO
    212 
    213220       CALL cpu_log( log_point_s(44), 'lpm_advec', 'start' )
    214 
    215 !
    216 !--    Initialize the switch used for the loop exit condition checked at the
    217 !--    end of this loop.
    218 !--    If at least one particle has failed to reach the LES timestep, this
    219 !--    switch will be set false.
    220        dt_3d_reached_l = .TRUE.
    221 
    222 !
    223 !--    Particle advection
    224        CALL lpm_advec
    225 
    226 !
    227 !--    Particle reflection from walls
    228        CALL lpm_boundary_conds( 'walls' )
    229 
    230 !
    231 !--    User-defined actions after the calculation of the new particle position
    232        CALL user_lpm_advec
     221       CALL cpu_log( log_point_s(44), 'lpm_advec', 'pause' )
     222!
     223!--    If particle advection includes SGS velocity components, calculate the
     224!--    required SGS quantities (i.e. gradients of the TKE, as well as
     225!--    horizontally averaged profiles of the SGS TKE and the resolved-scale
     226!--    velocity variances)
     227
     228       IF ( use_sgs_for_particles )  CALL lpm_init_sgs_tke
     229
     230       DO  i = nxl, nxr
     231          DO  j = nys, nyn
     232             DO  k = nzb+1, nzt
     233
     234                number_of_particles = prt_count(k,j,i)
     235!
     236!--             If grid cell gets empty, flag must be true
     237                IF ( number_of_particles <= 0 )  THEN
     238                   grid_particles(k,j,i)%time_loop_done = .TRUE.
     239                   CYCLE
     240                ENDIF
     241
     242                IF ( .NOT. first_loop_stride  .AND.  &
     243                     grid_particles(k,j,i)%time_loop_done ) CYCLE
     244
     245                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
     246
     247                particles(1:number_of_particles)%particle_mask = .TRUE.
     248!
     249!--             Initialize the variable storing the total time that a particle
     250!--             has advanced within the timestep procedure
     251                IF ( first_loop_stride )  THEN
     252                   particles(1:number_of_particles)%dt_sum = 0.0_wp
     253                ENDIF
     254!
     255!--             Particle (droplet) growth by condensation/evaporation and
     256!--             collision
     257                IF ( cloud_droplets  .AND.  first_loop_stride)  THEN
     258!
     259!--                Droplet growth by condensation / evaporation
     260                   CALL lpm_droplet_condensation(i,j,k)
     261!
     262!--                Particle growth by collision
     263                   IF ( collision_kernel /= 'none' )  THEN
     264                      CALL lpm_droplet_collision(i,j,k)
     265                   ENDIF
     266
     267                ENDIF
     268!
     269!--             Initialize the switch used for the loop exit condition checked
     270!--             at the end of this loop. If at least one particle has failed to
     271!--             reach the LES timestep, this switch will be set false in
     272!--             lpm_advec.
     273                dt_3d_reached_l = .TRUE.
     274
     275!
     276!--             Particle advection
     277                CALL lpm_advec(i,j,k)
     278!
     279!--             Particle reflection from walls
     280                IF ( topography /= 'flat' )  THEN
     281                   CALL lpm_boundary_conds( 'walls' )
     282                ENDIF
     283!
     284!--             User-defined actions after the calculation of the new particle
     285!--             position
     286                CALL user_lpm_advec
     287!
     288!--             Apply boundary conditions to those particles that have crossed
     289!--             the top or bottom boundary and delete those particles, which are
     290!--             older than allowed
     291                CALL lpm_boundary_conds( 'bottom/top' )
     292!
     293!---            If not all particles of the actual grid cell have reached the
     294!--             LES timestep, this cell has to to another loop iteration. Due to
     295!--             the fact that particles can move into neighboring grid cell,
     296!--             these neighbor cells also have to perform another loop iteration
     297                IF ( .NOT. dt_3d_reached_l )  THEN
     298                   ks = MAX(nzb+1,k)
     299                   ke = MIN(nzt,k)
     300                   js = MAX(nys,j)
     301                   je = MIN(nyn,j)
     302                   is = MAX(nxl,i)
     303                   ie = MIN(nxr,i)
     304                   grid_particles(ks:ke,js:je,is:ie)%time_loop_done = .FALSE.
     305                ENDIF
     306
     307             ENDDO
     308          ENDDO
     309       ENDDO
     310
     311       steps = steps + 1
     312       dt_3d_reached_l = ALL(grid_particles(:,:,:)%time_loop_done)
    233313
    234314!
     
    250330
    251331!
    252 !--    If necessary, release new set of particles
    253        IF ( time_prel >= dt_prel  .AND.  end_time_prel > simulated_time  .AND. &
    254             dt_3d_reached )  THEN
    255 
    256           CALL lpm_release_set
    257 
    258 !
    259 !--       The MOD function allows for changes in the output interval with
    260 !--       restart runs.
    261           time_prel = MOD( time_prel, MAX( dt_prel, dt_3d ) )
    262 
    263        ENDIF
     332!--    Move Particles local to PE to a different grid cell
     333       CALL lpm_move_particle
    264334
    265335!
     
    268338
    269339!
    270 !--    Apply boundary conditions to those particles that have crossed the top or
    271 !--    bottom boundary and delete those particles, which are older than allowed
    272        CALL lpm_boundary_conds( 'bottom/top' )
    273 
    274 !
    275340!--    Pack particles (eliminate those marked for deletion),
    276341!--    determine new number of particles
    277        IF ( number_of_particles > 0  .AND.  deleted_particles > 0 )  THEN
    278           CALL lpm_pack_arrays
    279        ENDIF
    280 
    281 !
    282 !--    Initialize variables for the next (sub-) timestep, i.e. for marking those
    283 !--    particles to be deleted after the timestep
    284        particle_mask     = .TRUE.
     342       CALL lpm_pack_all_arrays
     343
     344!
     345!--    Initialize variables for the next (sub-) timestep, i.e., for marking
     346!--    those particles to be deleted after the timestep
    285347       deleted_particles = 0
    286348
     
    293355       IF ( dt_3d_reached )  EXIT
    294356
     357       first_loop_stride = .FALSE.
    295358    ENDDO   ! timestep loop
    296359
    297 
    298 !
    299 !-- Sort particles in the sequence the gridboxes are stored in the memory
    300     time_sort_particles = time_sort_particles + dt_3d
    301     IF ( time_sort_particles >= dt_sort_particles )  THEN
    302        CALL lpm_sort_arrays
    303        time_sort_particles = MOD( time_sort_particles, &
    304                                   MAX( dt_sort_particles, dt_3d ) )
    305     ENDIF
    306 
    307 
    308360!
    309361!-- Calculate the new liquid water content for each grid box
    310     IF ( cloud_droplets )  CALL lpm_calc_liquid_water_content
     362    IF ( cloud_droplets )  THEN
     363       CALL lpm_calc_liquid_water_content
     364    ENDIF
     365
    311366
    312367
     
    325380
    326381!
     382!-- particle tails currently not available
     383!
    327384!-- If required, add the current particle positions to the particle tails
    328     IF ( use_particle_tails )  CALL lpm_extend_tails
     385!   IF ( use_particle_tails )  CALL lpm_extend_tails
    329386
    330387
     
    336393    CALL cpu_log( log_point(25), 'lpm', 'stop' )
    337394
    338 
    339395 END SUBROUTINE lpm
Note: See TracChangeset for help on using the changeset viewer.