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

Last change on this file since 622 was 622, checked in by raasch, 13 years ago

New:
---

Optional barriers included in order to speed up collective operations
MPI_ALLTOALL and MPI_ALLREDUCE. This feature is controlled with new initial
parameter collective_wait. Default is .FALSE, but .TRUE. on SGI-type
systems. (advec_particles, advec_s_bc, buoyancy, check_for_restart,
cpu_statistics, data_output_2d, data_output_ptseries, flow_statistics,
global_min_max, inflow_turbulence, init_3d_model, init_particles, init_pegrid,
init_slope, parin, pres, poismg, set_particle_attributes, timestep,
read_var_list, user_statistics, write_compressed, write_var_list)

Adjustments for Kyushu Univ. (lcrte, ibmku). Concerning hybrid
(MPI/openMP) runs, the number of openMP threads per MPI tasks can now
be given as an argument to mrun-option -O. (mbuild, mrun, subjob)

Changed:


Initialization of the module command changed for SGI-ICE/lcsgi (mbuild, subjob)

Errors:


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