source: palm/tags/release-3.1c/SOURCE/data_output_ptseries.f90 @ 1320

Last change on this file since 1320 was 4, checked in by raasch, 17 years ago

Id keyword set as property for all *.f90 files

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