source: palm/trunk/SOURCE/lpm_extend_tails.f90 @ 1682

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 4.7 KB
Line 
1!> @file lpm_extend_tails.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! ------------------
21! Code annotations made doxygen readable
22!
23! Former revisions:
24! -----------------
25! $Id: lpm_extend_tails.f90 1682 2015-10-07 23:56:08Z knoop $
26!
27! 1359 2014-04-11 17:15:14Z hoffmann
28! New particle structure integrated.
29! Kind definition added to all floating point numbers.
30!
31! 1320 2014-03-20 08:40:49Z raasch
32! ONLY-attribute added to USE-statements,
33! kind-parameters added to all INTEGER and REAL declaration statements,
34! kinds are defined in new module kinds,
35! comment fields (!:) to be used for variable explanations added to
36! all variable declaration statements
37!
38! 1036 2012-10-22 13:43:42Z raasch
39! code put under GPL (PALM 3.9)
40!
41! 849 2012-03-15 10:35:09Z raasch
42! initial revision (former part of advec_particles)
43!
44!
45! Description:
46! ------------
47!> Add the current particle positions to the particle tails.
48!------------------------------------------------------------------------------!
49 SUBROUTINE lpm_extend_tails
50 
51
52    USE control_parameters,                                                    &
53        ONLY:  dt_3d
54
55    USE kinds
56
57    USE particle_attributes,                                                   &
58        ONLY:  maximum_number_of_tailpoints, maximum_tailpoint_age,            &
59               minimum_tailpoint_distance, number_of_particles, particles,     &
60               particle_tail_coordinates
61
62    IMPLICIT NONE
63
64    INTEGER(iwp) ::  i       !<
65    INTEGER(iwp) ::  n       !<
66    INTEGER(iwp) ::  nn      !<
67
68    REAL(wp) ::  distance    !<
69
70
71    distance = 0.0_wp
72
73    DO  n = 1, number_of_particles
74
75       nn = particles(n)%tail_id
76
77       IF ( nn /= 0 )  THEN
78!
79!--       Calculate the distance between the actual particle position and the
80!--       next tailpoint
81          IF ( minimum_tailpoint_distance /= 0.0_wp )  THEN
82             distance = ( particle_tail_coordinates(1,1,nn) -      &
83                          particle_tail_coordinates(2,1,nn) )**2 + &
84                        ( particle_tail_coordinates(1,2,nn) -      &
85                          particle_tail_coordinates(2,2,nn) )**2 + &
86                        ( particle_tail_coordinates(1,3,nn) -      &
87                          particle_tail_coordinates(2,3,nn) )**2
88          ENDIF
89
90!
91!--       First, increase the index of all existings tailpoints by one
92          IF ( distance >= minimum_tailpoint_distance )  THEN
93
94             DO  i = particles(n)%tailpoints, 1, -1
95                particle_tail_coordinates(i+1,:,nn) = &
96                                               particle_tail_coordinates(i,:,nn)
97             ENDDO
98!
99!--          Increase the counter which contains the number of tailpoints.
100!--          This must always be smaller than the given maximum number of
101!--          tailpoints because otherwise the index bounds of
102!--          particle_tail_coordinates would be exceeded
103             IF ( particles(n)%tailpoints < maximum_number_of_tailpoints-1 ) &
104             THEN
105                particles(n)%tailpoints = particles(n)%tailpoints + 1
106             ENDIF
107          ENDIF
108!
109!--       In any case, store the new point at the beginning of the tail
110          particle_tail_coordinates(1,1,nn) = particles(n)%x
111          particle_tail_coordinates(1,2,nn) = particles(n)%y
112          particle_tail_coordinates(1,3,nn) = particles(n)%z
113          particle_tail_coordinates(1,4,nn) = particles(n)%class
114!
115!--       Increase the age of the tailpoints
116          IF ( minimum_tailpoint_distance /= 0.0_wp )  THEN
117             particle_tail_coordinates(2:particles(n)%tailpoints,5,nn) =    &
118               particle_tail_coordinates(2:particles(n)%tailpoints,5,nn) + dt_3d
119!
120!--          Delete the last tailpoint, if it has exceeded its maximum age
121             IF ( particle_tail_coordinates(particles(n)%tailpoints,5,nn) > &
122                  maximum_tailpoint_age )  THEN
123                particles(n)%tailpoints = particles(n)%tailpoints - 1
124             ENDIF
125          ENDIF
126
127       ENDIF
128
129    ENDDO
130
131
132 END SUBROUTINE lpm_extend_tails
Note: See TracBrowser for help on using the repository browser.