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

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

New:
---

droplet growth by condensation may include curvature and solution effects.
Steered by new inipar-parameter curvature_solution_effects.
(advec_particles, check_parameters, header, init_cloud_physics, init_particles, modules, parin, read_var_list, write_var_list)

mean/min/max particle radius added as output quantity. (data_output_ptseries, modules)

Changed:


Initialisation of temporary particle array for resorting removed.
(advec_particles)

particle attributes speed_x|y|z_sgs renamed rvar1|2|3.
(advec_particles, data_output_ptseries, modules, init_particles, particle_boundary_conds)

routine wang_kernel and respective module renamed lpm_collision_kernels.
Package (particle) parameters wang_collision_kernel and turbulence_effects_on_collision
replaced by parameter collision_kernel.
(Makefile, advec_particles, check_parameters, diffusion_e, init_3d_model, modules, package_parin, time_integration, new: lpm_collision_kernels, deleted: wang_kernel)

Errors:


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