source: palm/trunk/SOURCE/data_output_ptseries.f90 @ 824

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

preliminary checkin of new curvature/solution effects on droplet growth

  • Property svn:keywords set to Id
File size: 11.4 KB
Line 
1 SUBROUTINE data_output_ptseries
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! mean particle radius added as output quantity.
7! particle attributes speed_x|y|z_sgs renamed rvar1|2|3.
8!
9! Former revisions:
10! -----------------
11! $Id: data_output_ptseries.f90 824 2012-02-17 09:09:57Z raasch $
12!
13! 622 2010-12-10 08:08:13Z raasch
14! optional barriers included in order to speed up collective operations
15!
16! 291 2009-04-16 12:07:26Z raasch
17! simulated_time in NetCDF output replaced by time_since_reference_point.
18! Output of NetCDF messages with aid of message handling routine.
19!
20! 60 2007-03-11 11:50:04Z raasch
21! Particles-package is now part of the default code.
22!
23! RCS Log replace by Id keyword, revision history cleaned up
24!
25! Revision 1.2  2006/08/22 13:51:13  raasch
26! Seperate output for particle groups
27!
28! Revision 1.1  2006/08/04 14:24:18  raasch
29! Initial revision
30!
31!
32! Description:
33! ------------
34! Output of particle data timeseries in NetCDF format.
35!------------------------------------------------------------------------------!
36
37    USE control_parameters
38    USE cpulog
39    USE indices
40    USE interfaces
41    USE netcdf_control
42    USE particle_attributes
43    USE pegrid
44
45    IMPLICIT NONE
46
47
48    INTEGER ::  i, inum, j, n
49
50    REAL, DIMENSION(0:number_of_particle_groups,30) ::  pts_value, pts_value_l
51
52
53
54    CALL cpu_log( log_point(36), 'data_output_ptseries', 'start' )
55
56    IF ( myid == 0  .AND.  netcdf_output )  THEN
57!
58!--    Open file for time series output in NetCDF format
59       dopts_time_count = dopts_time_count + 1
60       CALL check_open( 109 )
61#if defined( __netcdf )
62!
63!--    Update the particle time series time axis
64       nc_stat = NF90_PUT_VAR( id_set_pts, id_var_time_pts,      &
65                               (/ time_since_reference_point /), &
66                               start = (/ dopts_time_count /), count = (/ 1 /) )
67       CALL handle_netcdf_error( 'data_output_ptseries', 391 )
68#endif
69
70    ENDIF
71
72    pts_value_l = 0.0
73
74!
75!-- Calculate or collect the particle time series quantities for all particles
76!-- and seperately for each particle group (if there is more than one group)
77    DO  n = 1, number_of_particles
78
79       pts_value_l(0,1)  = number_of_particles            ! total # of particles
80       pts_value_l(0,2)  = pts_value_l(0,2) + &
81                           ( particles(n)%x - particles(n)%origin_x )  ! mean x
82       pts_value_l(0,3)  = pts_value_l(0,3) + &
83                           ( particles(n)%y - particles(n)%origin_y )  ! mean y
84       pts_value_l(0,4)  = pts_value_l(0,4) + &
85                           ( particles(n)%z - particles(n)%origin_z )  ! mean z
86       pts_value_l(0,5)  = pts_value_l(0,5) + particles(n)%z ! mean z (absolute)
87       pts_value_l(0,6)  = pts_value_l(0,6) + particles(n)%speed_x     ! mean u
88       pts_value_l(0,7)  = pts_value_l(0,7) + particles(n)%speed_y     ! mean v
89       pts_value_l(0,8)  = pts_value_l(0,8) + particles(n)%speed_z     ! mean w
90       pts_value_l(0,9)  = pts_value_l(0,9) + particles(n)%rvar1     ! mean sgsu
91       pts_value_l(0,10) = pts_value_l(0,10) + particles(n)%rvar2    ! mean sgsv
92       pts_value_l(0,11) = pts_value_l(0,11) + particles(n)%rvar3    ! mean sgsw
93       IF ( particles(n)%speed_z > 0.0 )  THEN
94          pts_value_l(0,12) = pts_value_l(0,12) + 1.0  ! # of upward moving prts
95          pts_value_l(0,13) = pts_value_l(0,13) + &
96                                            particles(n)%speed_z ! mean w upw.
97       ELSE
98          pts_value_l(0,14) = pts_value_l(0,14) + &
99                                            particles(n)%speed_z ! mean w down
100       ENDIF
101       pts_value_l(0,15) = pts_value_l(0,15) + particles(n)%radius
102       pts_value_l(0,16) = number_of_particles
103       pts_value_l(0,17) = number_of_particles
104
105!
106!--    Repeat the same for the respective particle group
107       IF ( number_of_particle_groups > 1 )  THEN
108          j = particles(n)%group
109
110          pts_value_l(j,1)  = pts_value_l(j,1)  + 1
111          pts_value_l(j,2)  = pts_value_l(j,2)  + &
112                              ( particles(n)%x - particles(n)%origin_x )
113          pts_value_l(j,3)  = pts_value_l(j,3)  + &
114                              ( particles(n)%y - particles(n)%origin_y )
115          pts_value_l(j,4)  = pts_value_l(j,4)  + &
116                              ( particles(n)%z - particles(n)%origin_z )
117          pts_value_l(j,5)  = pts_value_l(j,5)  + particles(n)%z
118          pts_value_l(j,6)  = pts_value_l(j,6)  + particles(n)%speed_x
119          pts_value_l(j,7)  = pts_value_l(j,7)  + particles(n)%speed_y
120          pts_value_l(j,8)  = pts_value_l(j,8)  + particles(n)%speed_z
121          pts_value_l(j,9)  = pts_value_l(j,9)  + particles(n)%rvar1
122          pts_value_l(j,10) = pts_value_l(j,10) + particles(n)%rvar2
123          pts_value_l(j,11) = pts_value_l(j,11) + particles(n)%rvar3
124          IF ( particles(n)%speed_z > 0.0 )  THEN
125             pts_value_l(j,12) = pts_value_l(j,12) + 1.0
126             pts_value_l(j,13) = pts_value_l(j,13) + particles(n)%speed_z
127          ELSE
128             pts_value_l(j,14) = pts_value_l(j,14) + particles(n)%speed_z
129          ENDIF
130          pts_value_l(j,15) = pts_value_l(j,15) + particles(n)%radius
131          pts_value_l(j,16) = pts_value_l(j,16) + 1.0
132          pts_value_l(j,17) = pts_value_l(j,17) + 1.0
133
134       ENDIF
135
136    ENDDO
137
138#if defined( __parallel )
139!
140!-- Sum values of the subdomains
141    inum = number_of_particle_groups + 1
142
143    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
144    CALL MPI_ALLREDUCE( pts_value_l(0,1), pts_value(0,1), 15*inum, MPI_REAL, &
145                        MPI_SUM, comm2d, ierr )
146    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
147    CALL MPI_ALLREDUCE( pts_value_l(0,16), pts_value(0,16), inum, MPI_REAL, &
148                        MPI_MAX, comm2d, ierr )
149    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
150    CALL MPI_ALLREDUCE( pts_value_l(0,17), pts_value(0,17), inum, MPI_REAL, &
151                        MPI_MIN, comm2d, ierr )
152#else
153    pts_value(:,1:17) = pts_value_l(:,1:17)
154#endif
155
156!
157!-- Normalize the above calculated quantities with the total number of
158!-- particles
159    IF ( number_of_particle_groups > 1 )  THEN
160       inum = number_of_particle_groups
161    ELSE
162       inum = 0
163    ENDIF
164
165    DO  j = 0, inum
166
167       IF ( pts_value(j,1) > 0.0 )  THEN
168
169          pts_value(j,2:15) = pts_value(j,2:15) / pts_value(j,1)
170          IF ( pts_value(j,12) > 0.0  .AND.  pts_value(j,12) < 1.0 )  THEN
171             pts_value(j,13) = pts_value(j,13) / pts_value(j,12)
172             pts_value(j,14) = pts_value(j,14) / ( 1.0 - pts_value(j,12) )
173          ELSEIF ( pts_value(j,12) == 0.0 )  THEN
174             pts_value(j,13) = -1.0
175          ELSE
176             pts_value(j,14) = -1.0
177          ENDIF
178
179       ENDIF
180
181    ENDDO
182
183!
184!-- Calculate higher order moments of particle time series quantities,
185!-- seperately for each particle group (if there is more than one group)
186    DO  n = 1, number_of_particles
187
188       pts_value_l(0,18) = pts_value_l(0,18) + ( particles(n)%x - &
189                           particles(n)%origin_x - pts_value(0,2) )**2 ! x*2
190       pts_value_l(0,19) = pts_value_l(0,19) + ( particles(n)%y - &
191                           particles(n)%origin_y - pts_value(0,3) )**2 ! y*2
192       pts_value_l(0,20) = pts_value_l(0,20) + ( particles(n)%z - &
193                           particles(n)%origin_z - pts_value(0,4) )**2 ! z*2
194       pts_value_l(0,21) = pts_value_l(0,21) + ( particles(n)%speed_x - &
195                                               pts_value(0,6) )**2     ! u*2
196       pts_value_l(0,22) = pts_value_l(0,22) + ( particles(n)%speed_y - &
197                                               pts_value(0,7) )**2     ! v*2
198       pts_value_l(0,23) = pts_value_l(0,23) + ( particles(n)%speed_z - &
199                                               pts_value(0,8) )**2     ! w*2
200       pts_value_l(0,24) = pts_value_l(0,24) + ( particles(n)%rvar1 - &
201                                               pts_value(0,9) )**2     ! u"2
202       pts_value_l(0,25) = pts_value_l(0,25) + ( particles(n)%rvar2 - &
203                                               pts_value(0,10) )**2    ! v"2
204       pts_value_l(0,26) = pts_value_l(0,26) + ( particles(n)%rvar3 - &
205                                               pts_value(0,11) )**2    ! w"2
206!
207!--    Repeat the same for the respective particle group
208       IF ( number_of_particle_groups > 1 )  THEN
209          j = particles(n)%group
210
211          pts_value_l(j,18) = pts_value_l(j,18) + ( particles(n)%x - &
212                              particles(n)%origin_x - pts_value(j,2) )**2
213          pts_value_l(j,19) = pts_value_l(j,19) + ( particles(n)%y - &
214                              particles(n)%origin_y - pts_value(j,3) )**2
215          pts_value_l(j,20) = pts_value_l(j,20) + ( particles(n)%z - &
216                              particles(n)%origin_z - pts_value(j,4) )**2
217          pts_value_l(j,21) = pts_value_l(j,21) + ( particles(n)%speed_x - &
218                                                  pts_value(j,6) )**2
219          pts_value_l(j,22) = pts_value_l(j,22) + ( particles(n)%speed_y - &
220                                                  pts_value(j,7) )**2
221          pts_value_l(j,23) = pts_value_l(j,23) + ( particles(n)%speed_z - &
222                                                  pts_value(j,8) )**2
223          pts_value_l(j,24) = pts_value_l(j,24) + ( particles(n)%rvar1 -   &
224                                                  pts_value(j,9) )**2
225          pts_value_l(j,25) = pts_value_l(j,25) + ( particles(n)%rvar2 -   &
226                                                  pts_value(j,10) )**2
227          pts_value_l(j,26) = pts_value_l(j,26) + ( particles(n)%rvar3 -   &
228                                                  pts_value(j,11) )**2
229       ENDIF
230
231    ENDDO
232
233    pts_value_l(0,27) = ( number_of_particles - pts_value(0,1) / numprocs )**2
234                                                 ! variance of particle numbers
235    IF ( number_of_particle_groups > 1 )  THEN
236       DO  j = 1, number_of_particle_groups
237          pts_value_l(j,27) = ( pts_value_l(j,1) - &
238                                pts_value(j,1) / numprocs )**2
239       ENDDO
240    ENDIF
241
242#if defined( __parallel )
243!
244!-- Sum values of the subdomains
245    inum = number_of_particle_groups + 1
246
247    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
248    CALL MPI_ALLREDUCE( pts_value_l(0,18), pts_value(0,18), inum*10, MPI_REAL, &
249                        MPI_SUM, comm2d, ierr )
250#else
251    pts_value(:,18:27) = pts_value_l(:,18:27)
252#endif
253
254!
255!-- Normalize the above calculated quantities with the total number of
256!-- particles
257    IF ( number_of_particle_groups > 1 )  THEN
258       inum = number_of_particle_groups
259    ELSE
260       inum = 0
261    ENDIF
262
263    DO  j = 0, inum
264
265       IF ( pts_value(j,1) > 0.0 )  THEN
266          pts_value(j,18:26) = pts_value(j,18:26) / pts_value(j,1)
267       ENDIF
268       pts_value(j,27) = pts_value(j,27) / numprocs
269
270    ENDDO
271
272#if defined( __netcdf )
273!
274!-- Output particle time series quantities in NetCDF format
275    IF ( myid == 0  .AND.  netcdf_output )  THEN
276       DO  j = 0, inum
277          DO  i = 1, dopts_num
278             nc_stat = NF90_PUT_VAR( id_set_pts, id_var_dopts(i,j),  &
279                                     (/ pts_value(j,i) /),           &
280                                     start = (/ dopts_time_count /), &
281                                     count = (/ 1 /) )
282             CALL handle_netcdf_error( 'data_output_ptseries', 392 )
283          ENDDO
284       ENDDO
285    ENDIF
286#endif
287
288    CALL cpu_log( log_point(36), 'data_output_ptseries','stop', 'nobarrier' )
289
290 END SUBROUTINE data_output_ptseries
Note: See TracBrowser for help on using the repository browser.