source: palm/trunk/SOURCE/lpm_data_output_particles.f90 @ 849

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

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

  • Property svn:keywords set to Id
File size: 7.2 KB
Line 
1 SUBROUTINE lpm_data_output_particles
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_data_output_particles.f90 849 2012-03-15 10:35:09Z raasch $
11!
12! 22/02/12 - Initial version
13!
14! Description:
15! ------------
16! Write particle data in FORTRAN binary and/or netCDF format
17!------------------------------------------------------------------------------!
18
19    USE control_parameters
20    USE cpulog
21    USE interfaces
22    USE netcdf_control
23    USE particle_attributes
24
25    IMPLICIT NONE
26
27
28    CALL cpu_log( log_point_s(40), 'lpm_data_output', 'start' )
29
30!
31!-- Attention: change version number for unit 85 (in routine check_open)
32!--            whenever the output format for this unit is changed!
33    CALL check_open( 85 )
34
35    WRITE ( 85 )  simulated_time, maximum_number_of_particles, &
36                  number_of_particles
37    WRITE ( 85 )  particles
38    WRITE ( 85 )  maximum_number_of_tailpoints, maximum_number_of_tails, &
39                  number_of_tails
40    IF ( maximum_number_of_tails > 0 )  THEN
41       WRITE ( 85 )  particle_tail_coordinates
42    ENDIF
43
44    CALL close_file( 85 )
45
46
47#if defined( __netcdf )
48!
49!-- Output in netCDF format
50    IF ( netcdf_output )  THEN
51
52       CALL check_open( 108 )
53
54!
55!--    Update the NetCDF time axis
56       prt_time_count = prt_time_count + 1
57
58       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_time_prt, &
59                               (/ simulated_time /),        &
60                               start = (/ prt_time_count /), count = (/ 1 /) )
61       CALL handle_netcdf_error( 'lpm_data_output_particles', 1 )
62
63!
64!--    Output the real number of particles used
65       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_rnop_prt, &
66                               (/ number_of_particles /),   &
67                               start = (/ prt_time_count /), count = (/ 1 /) )
68       CALL handle_netcdf_error( 'lpm_data_output_particles', 2 )
69
70!
71!--    Output all particle attributes
72       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(1), particles%age,      &
73                               start = (/ 1, prt_time_count /),               &
74                               count = (/ maximum_number_of_particles /) )
75       CALL handle_netcdf_error( 'lpm_data_output_particles', 3 )
76
77       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(2), particles%dvrp_psize,&
78                               start = (/ 1, prt_time_count /),                &
79                               count = (/ maximum_number_of_particles /) )
80       CALL handle_netcdf_error( 'lpm_data_output_particles', 4 )
81
82       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(3), particles%origin_x, &
83                               start = (/ 1, prt_time_count /),               &
84                               count = (/ maximum_number_of_particles /) )
85       CALL handle_netcdf_error( 'lpm_data_output_particles', 5 )
86
87       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(4), particles%origin_y, &
88                               start = (/ 1, prt_time_count /),               &
89                               count = (/ maximum_number_of_particles /) )
90       CALL handle_netcdf_error( 'lpm_data_output_particles', 6 )
91
92       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(5), particles%origin_z, &
93                               start = (/ 1, prt_time_count /),               &
94                               count = (/ maximum_number_of_particles /) )
95       CALL handle_netcdf_error( 'lpm_data_output_particles', 7 )
96
97       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(6), particles%radius,   &
98                               start = (/ 1, prt_time_count /),               &
99                               count = (/ maximum_number_of_particles /) )
100       CALL handle_netcdf_error( 'lpm_data_output_particles', 8 )
101
102       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(7), particles%speed_x,  &
103                               start = (/ 1, prt_time_count /),               &
104                               count = (/ maximum_number_of_particles /) )
105       CALL handle_netcdf_error( 'lpm_data_output_particles', 9 )
106
107       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(8), particles%speed_y,  &
108                               start = (/ 1, prt_time_count /),               &
109                               count = (/ maximum_number_of_particles /) )
110       CALL handle_netcdf_error( 'lpm_data_output_particles', 10 )
111
112       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(9), particles%speed_z,  &
113                               start = (/ 1, prt_time_count /),               &
114                               count = (/ maximum_number_of_particles /) )
115       CALL handle_netcdf_error( 'lpm_data_output_particles', 11 )
116
117       nc_stat = NF90_PUT_VAR( id_set_prt,id_var_prt(10),                     &
118                               particles%weight_factor,                       &
119                               start = (/ 1, prt_time_count /),               &
120                               count = (/ maximum_number_of_particles /) )
121       CALL handle_netcdf_error( 'lpm_data_output_particles', 12 )
122
123       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(11), particles%x,       &
124                               start = (/ 1, prt_time_count /),               &
125                               count = (/ maximum_number_of_particles /) )
126       CALL handle_netcdf_error( 'lpm_data_output_particles', 13 )
127
128       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(12), particles%y,       & 
129                               start = (/ 1, prt_time_count /),               &
130                               count = (/ maximum_number_of_particles /) )
131       CALL handle_netcdf_error( 'lpm_data_output_particles', 14 )
132
133       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(13), particles%z,       &
134                               start = (/ 1, prt_time_count /),               &
135                               count = (/ maximum_number_of_particles /) )
136       CALL handle_netcdf_error( 'lpm_data_output_particles', 15 )
137
138       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(14), particles%class,   &
139                               start = (/ 1, prt_time_count /),               &
140                               count = (/ maximum_number_of_particles /) )
141       CALL handle_netcdf_error( 'lpm_data_output_particles', 16 )
142
143       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(15), particles%group,   &
144                               start = (/ 1, prt_time_count /),               &
145                               count = (/ maximum_number_of_particles /) )
146       CALL handle_netcdf_error( 'lpm_data_output_particles', 17 )
147
148       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(16),                    &
149                               particles%tailpoints,                          &
150                               start = (/ 1, prt_time_count /),               &
151                               count = (/ maximum_number_of_particles /) )
152       CALL handle_netcdf_error( 'lpm_data_output_particles', 18 )
153
154       nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(17), particles%tail_id, &
155                               start = (/ 1, prt_time_count /),               &
156                               count = (/ maximum_number_of_particles /) )
157       CALL handle_netcdf_error( 'lpm_data_output_particles', 19 )
158
159    ENDIF
160
161#endif
162
163    CALL cpu_log( log_point_s(40), 'lpm_data_output', 'stop' )
164
165 END SUBROUTINE lpm_data_output_particles
Note: See TracBrowser for help on using the repository browser.