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

Last change on this file since 264 was 263, checked in by heinze, 15 years ago

Output of NetCDF messages with aid of message handling routine.

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