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

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

last commit documented

  • Property svn:keywords set to Id
File size: 3.0 KB
Line 
1 SUBROUTINE lpm_extend_tails
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_extend_tails.f90 850 2012-03-15 12:09:25Z raasch $
11!
12! 849 2012-03-15 10:35:09Z raasch
13! initial revision (former part of advec_particles)
14!
15!
16! Description:
17! ------------
18! Add the current particle positions to the particle tails.
19!------------------------------------------------------------------------------!
20
21    USE control_parameters
22    USE particle_attributes
23
24    IMPLICIT NONE
25
26    INTEGER ::  i, n, nn
27
28    REAL ::  distance
29
30
31    distance = 0.0
32
33    DO  n = 1, number_of_particles
34
35       nn = particles(n)%tail_id
36
37       IF ( nn /= 0 )  THEN
38!
39!--       Calculate the distance between the actual particle position and the
40!--       next tailpoint
41          IF ( minimum_tailpoint_distance /= 0.0 )  THEN
42             distance = ( particle_tail_coordinates(1,1,nn) -      &
43                          particle_tail_coordinates(2,1,nn) )**2 + &
44                        ( particle_tail_coordinates(1,2,nn) -      &
45                          particle_tail_coordinates(2,2,nn) )**2 + &
46                        ( particle_tail_coordinates(1,3,nn) -      &
47                          particle_tail_coordinates(2,3,nn) )**2
48          ENDIF
49
50!
51!--       First, increase the index of all existings tailpoints by one
52          IF ( distance >= minimum_tailpoint_distance )  THEN
53
54             DO  i = particles(n)%tailpoints, 1, -1
55                particle_tail_coordinates(i+1,:,nn) = &
56                                               particle_tail_coordinates(i,:,nn)
57             ENDDO
58!
59!--          Increase the counter which contains the number of tailpoints.
60!--          This must always be smaller than the given maximum number of
61!--          tailpoints because otherwise the index bounds of
62!--          particle_tail_coordinates would be exceeded
63             IF ( particles(n)%tailpoints < maximum_number_of_tailpoints-1 ) &
64             THEN
65                particles(n)%tailpoints = particles(n)%tailpoints + 1
66             ENDIF
67          ENDIF
68!
69!--       In any case, store the new point at the beginning of the tail
70          particle_tail_coordinates(1,1,nn) = particles(n)%x
71          particle_tail_coordinates(1,2,nn) = particles(n)%y
72          particle_tail_coordinates(1,3,nn) = particles(n)%z
73          particle_tail_coordinates(1,4,nn) = particles(n)%class
74!
75!--       Increase the age of the tailpoints
76          IF ( minimum_tailpoint_distance /= 0.0 )  THEN
77             particle_tail_coordinates(2:particles(n)%tailpoints,5,nn) =    &
78               particle_tail_coordinates(2:particles(n)%tailpoints,5,nn) + dt_3d
79!
80!--          Delete the last tailpoint, if it has exceeded its maximum age
81             IF ( particle_tail_coordinates(particles(n)%tailpoints,5,nn) > &
82                  maximum_tailpoint_age )  THEN
83                particles(n)%tailpoints = particles(n)%tailpoints - 1
84             ENDIF
85          ENDIF
86
87       ENDIF
88
89    ENDDO
90
91
92 END SUBROUTINE lpm_extend_tails
Note: See TracBrowser for help on using the repository browser.