source: palm/trunk/SOURCE/lpm_release_set.f90 @ 849

Last change on this file since 849 was 849, checked in by raasch, 12 years ago

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

  • Property svn:keywords set to Id
File size: 5.2 KB
Line 
1 SUBROUTINE lpm_release_set
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_release_set.f90 849 2012-03-15 10:35:09Z raasch $
11!
12!
13! Description:
14! ------------
15! Release a new set of particles and, if required, particle tails. These
16! particles/tails are added at the end of the existing arrays. Extend the
17! respective particle and tail arrays, if neccessary.
18!------------------------------------------------------------------------------!
19
20    USE control_parameters
21    USE grid_variables
22    USE indices
23    USE particle_attributes
24    USE random_function_mod
25
26    IMPLICIT NONE
27
28    INTEGER ::  ie, is, n, nn
29
30
31!
32!-- Check, if particle storage must be extended
33    IF ( number_of_particles + number_of_initial_particles > &
34         maximum_number_of_particles  )  THEN
35       IF ( netcdf_output  .AND.  netcdf_data_format < 3 )  THEN
36          message_string = 'maximum_number_of_particles needs to be increa' // &
37                           'sed &but this is not allowed with netcdf_data_' // &
38                           'format < 3'
39          CALL message( 'lpm_release_set', 'PA0146', 2, 2, -1, 6, 1 )
40       ELSE
41          CALL lpm_extend_particle_array( number_of_initial_particles )
42       ENDIF
43    ENDIF
44
45!
46!-- Check, if tail storage must be extended
47    IF ( use_particle_tails )  THEN
48       IF ( number_of_tails + number_of_initial_tails > &
49            maximum_number_of_tails  )  THEN
50          IF ( netcdf_output  .AND.  netcdf_data_format < 3 )  THEN
51             message_string = 'maximum_number_of_tails needs to be increas' // &
52                              'ed &but this is not allowed with netcdf_dat' // &
53                              'a_format < 3'
54             CALL message( 'lpm_release_set', 'PA0147', 2, 2, -1, 6, 1 )
55          ELSE
56             CALL lpm_extend_tail_array( number_of_initial_tails )
57          ENDIF
58       ENDIF
59    ENDIF
60
61    IF ( number_of_initial_particles /= 0 )  THEN
62
63       is = number_of_particles + 1
64       ie = number_of_particles + number_of_initial_particles
65       particles(is:ie) = initial_particles(1:number_of_initial_particles)
66!
67!--    Add random fluctuation to particle positions. Particles should
68!--    remain in the subdomain.
69       IF ( random_start_position )  THEN
70
71          DO  n = is, ie
72
73             IF ( psl(particles(n)%group) /= psr(particles(n)%group) )  THEN
74                particles(n)%x = particles(n)%x +                         &
75                                 ( random_function( iran_part ) - 0.5 ) * &
76                                 pdx(particles(n)%group)
77                IF ( particles(n)%x  <=  ( nxl - 0.5 ) * dx )  THEN
78                   particles(n)%x = ( nxl - 0.4999999999 ) * dx
79                ELSEIF ( particles(n)%x  >=  ( nxr + 0.5 ) * dx )  THEN
80                   particles(n)%x = ( nxr + 0.4999999999 ) * dx
81                ENDIF
82             ENDIF
83
84             IF ( pss(particles(n)%group) /= psn(particles(n)%group) )  THEN
85                particles(n)%y = particles(n)%y +                         &
86                                 ( random_function( iran_part ) - 0.5 ) * &
87                                 pdy(particles(n)%group)
88                IF ( particles(n)%y  <=  ( nys - 0.5 ) * dy )  THEN
89                   particles(n)%y = ( nys - 0.4999999999 ) * dy
90                ELSEIF ( particles(n)%y  >=  ( nyn + 0.5 ) * dy )  THEN
91                   particles(n)%y = ( nyn + 0.4999999999 ) * dy
92                ENDIF
93             ENDIF
94
95             IF ( psb(particles(n)%group) /= pst(particles(n)%group) )  THEN
96                particles(n)%z = particles(n)%z +                         &
97                                 ( random_function( iran_part ) - 0.5 ) * &
98                                 pdz(particles(n)%group)
99             ENDIF
100
101          ENDDO
102
103       ENDIF
104
105!
106!--    Set the beginning of the new particle tails and their age
107       IF ( use_particle_tails )  THEN
108
109          DO  n = is, ie
110!
111!--          New particles which should have a tail, already have got a
112!--          provisional tail id unequal zero (see lpm_init)
113             IF ( particles(n)%tail_id /= 0 )  THEN
114
115                number_of_tails = number_of_tails + 1
116                nn = number_of_tails
117                particles(n)%tail_id = nn   ! set the final tail id
118                particle_tail_coordinates(1,1,nn) = particles(n)%x
119                particle_tail_coordinates(1,2,nn) = particles(n)%y
120                particle_tail_coordinates(1,3,nn) = particles(n)%z
121                particle_tail_coordinates(1,4,nn) = particles(n)%class
122                particles(n)%tailpoints = 1
123
124                IF ( minimum_tailpoint_distance /= 0.0 )  THEN
125                   particle_tail_coordinates(2,1,nn) = particles(n)%x
126                   particle_tail_coordinates(2,2,nn) = particles(n)%y
127                   particle_tail_coordinates(2,3,nn) = particles(n)%z
128                   particle_tail_coordinates(2,4,nn) = particles(n)%class
129                   particle_tail_coordinates(1:2,5,nn) = 0.0
130                   particles(n)%tailpoints = 2
131                ENDIF
132
133             ENDIF
134
135          ENDDO
136
137       ENDIF
138
139       number_of_particles = number_of_particles + number_of_initial_particles
140
141    ENDIF
142
143 END SUBROUTINE lpm_release_set
Note: See TracBrowser for help on using the repository browser.