Ignore:
Timestamp:
Jul 26, 2019 1:11:56 PM (5 years ago)
Author:
schwenkel
Message:

Implement reset method as bottom boundary condition

File:
1 edited

Legend:

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

    r4121 r4122  
    2525! -----------------
    2626! $Id$
     27! Implement reset method as bottom boundary condition
     28!
     29! 4121 2019-07-26 10:01:22Z schwenkel
    2730! Implementation of an simple method for interpolating the velocities to
    2831! particle position
     
    173176! Description:
    174177! ------------
     178!> The embedded LPM allows for studying transport and dispersion processes within
     179!> turbulent flows. This model including passive particles that do not show any
     180!> feedback on the turbulent flow. Further also particles with inertia and
     181!> cloud droplets ca be simulated explicitly.
    175182!>
     183!> @todo test lcm
     184!>       implement simple interpolation method for subgrid scale velocites
     185!> @note <Enter notes on the module>
     186!> @bug  <Enter bug on the module>
    176187!------------------------------------------------------------------------------!
    177188 MODULE lagrangian_particle_model_mod
     
    253264    USE NETCDF
    254265#endif
    255 
    256 
    257      USE arrays_3d,                                                             &
    258         ONLY:
    259 
    260     USE indices,                                                               &
    261         ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
    262 
    263     USE kinds
    264 
    265     USE pegrid
    266266
    267267    IMPLICIT NONE
     
    10741074       CASE ( 'reflect' )
    10751075          ibc_par_b = 2
     1076
     1077       CASE ( 'reset' )
     1078          ibc_par_b = 3
    10761079
    10771080       CASE DEFAULT
     
    43714374    INTEGER(iwp) ::  i2             !< grid index (x) of current particle position
    43724375    INTEGER(iwp) ::  i3             !< grid index (x) of intermediate particle position
     4376    INTEGER(iwp) ::  index_reset    !< index reset height
    43734377    INTEGER(iwp) ::  jr             !< dummy for sorting algorithmus
    43744378    INTEGER(iwp) ::  j1             !< grid index (y) of old particle position
     
    43794383    INTEGER(iwp) ::  k3             !< grid index (z) of intermediate particle position
    43804384    INTEGER(iwp) ::  n              !< particle number
     4385    INTEGER(iwp) ::  particles_top  !< maximum reset height
    43814386    INTEGER(iwp) ::  t_index        !< running index for intermediate particle timesteps in reflection algorithmus
    43824387    INTEGER(iwp) ::  t_index_number !< number of intermediate particle timesteps in reflection algorithmus
     
    44174422    REAL(wp) ::  prt_y          !< current particle position (y)
    44184423    REAL(wp) ::  prt_z          !< current particle position (z)
     4424    REAL(wp) ::  ran_val        !< location of wall in z
     4425    REAL(wp) ::  reset_top      !< location of wall in z
    44194426    REAL(wp) ::  t_old          !< previous reflection time
    44204427    REAL(wp) ::  tmp_t          !< dummy for sorting algorithmus
     
    44874494                     particles(n)%rvar3 < 0.0_wp )  THEN
    44884495                   particles(n)%rvar3 = -particles(n)%rvar3
     4496                ENDIF
     4497             ELSEIF ( ibc_par_b == 3 )  THEN
     4498!
     4499!--             Find reset height. @note this works only in non-strechted cases
     4500                particles_top = INT( pst(1) / dz(1) )
     4501                index_reset = MINLOC( prt_count(nzb+1:particles_top,j,i), DIM = 1 )
     4502                reset_top = zu(index_reset)
     4503                iran_part = iran_part + myid
     4504                ran_val = random_function( iran_part )
     4505                particles(n)%z       = reset_top *  ( 1.0  + ( ran_val / 10.0_wp) )
     4506                particles(n)%speed_z = 0.0_wp
     4507                IF ( curvature_solution_effects ) THEN
     4508                   particles(n)%radius = particles(n)%aux1
     4509                ELSE
     4510                   particles(n)%radius = 1.0E-8
    44894511                ENDIF
    44904512             ENDIF
Note: See TracChangeset for help on using the changeset viewer.