source: palm/trunk/SOURCE/data_output_mask.f90 @ 564

Last change on this file since 564 was 564, checked in by helmke, 13 years ago

several changes for an unlimited output of mask data and message IDs changed

  • Property svn:keywords set to Id
File size: 15.1 KB
Line 
1 SUBROUTINE data_output_mask( av )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! start number of mask output files changed to 201, netcdf message identifiers
7! of masked output changed, palm message identifiers of masked output changed
8!
9! Former revisions:
10! -----------------
11! $Id: data_output_mask.f90 564 2010-09-30 13:18:59Z helmke $
12!
13! 493 2010-03-01 08:30:24Z raasch
14! netcdf_format_mask* and format_parallel_io replaced by netcdf_data_format
15!
16! 475 2010-02-04 02:26:16Z raasch
17! Bugfix in serial branch: arguments from array local_pf removed in N90_PUT_VAR
18!
19! 410 2009-12-04 17:05:40Z letzel
20! Initial version
21!
22! Description:
23! ------------
24! Masked data output in NetCDF format for current mask (current value of mid).
25!------------------------------------------------------------------------------!
26
27#if defined( __netcdf )
28    USE arrays_3d
29    USE averaging
30    USE cloud_parameters
31    USE control_parameters
32    USE cpulog
33    USE grid_variables
34    USE indices
35    USE interfaces
36    USE netcdf
37    USE netcdf_control
38    USE particle_attributes
39    USE pegrid
40
41    IMPLICIT NONE
42
43    INTEGER ::  av, ngp, file_id, i, if, is, j, k, l, n, psi, s, sender, &
44                ind(6)
45    LOGICAL ::  found, resorted
46    REAL    ::  mean_r, s_r3, s_r4
47    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  local_pf
48#if defined( __parallel )
49    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  total_pf
50#endif
51    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
52
53!
54!-- Return, if nothing to output
55    IF ( domask_no(mid,av) == 0 )  RETURN
56
57    CALL cpu_log (log_point(49),'data_output_mask','start')
58
59!
60!-- Open output file.
61    IF ( netcdf_output  .AND.  ( myid == 0  .OR.  netcdf_data_format > 2 ) ) &
62    THEN
63       CALL check_open( 200+mid+av*max_masks )
64    ENDIF 
65
66!
67!-- Allocate total and local output arrays.
68#if defined( __parallel )
69    IF ( myid == 0 )  THEN
70       ALLOCATE( total_pf(mask_size(mid,1),mask_size(mid,2),mask_size(mid,3)) )
71    ENDIF
72#endif
73    ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
74                       mask_size_l(mid,3)) )
75
76!
77!-- Update the NetCDF time axis.
78    domask_time_count(mid,av) = domask_time_count(mid,av) + 1
79    IF ( netcdf_output  .AND.  ( myid == 0  .OR.  netcdf_data_format > 2 ) ) &
80    THEN
81       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_time_mask(mid,av), &
82                               (/ simulated_time /),                          &
83                               start = (/ domask_time_count(mid,av) /),       &
84                               count = (/ 1 /) )
85       CALL handle_netcdf_error( 'data_output_mask', 460 )
86    ENDIF
87
88!
89!-- Loop over all variables to be written.
90    if = 1
91
92    DO  WHILE ( domask(mid,av,if)(1:1) /= ' ' )
93!
94!--    Reallocate local_pf on PE 0 since its shape changes during MPI exchange
95       IF ( netcdf_data_format < 3   .AND.  myid == 0  .AND.  if > 1 )  THEN
96          DEALLOCATE( local_pf )
97          ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
98                             mask_size_l(mid,3)) )
99       ENDIF
100!
101!--    Store the variable chosen.
102       resorted = .FALSE.
103       SELECT CASE ( TRIM( domask(mid,av,if) ) )
104
105          CASE ( 'e' )
106             IF ( av == 0 )  THEN
107                to_be_resorted => e
108             ELSE
109                to_be_resorted => e_av
110             ENDIF
111
112          CASE ( 'p' )
113             IF ( av == 0 )  THEN
114                to_be_resorted => p
115             ELSE
116                to_be_resorted => p_av
117             ENDIF
118
119          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
120             IF ( av == 0 )  THEN
121                tend = prt_count
122                CALL exchange_horiz( tend )
123                DO  i = 1, mask_size_l(mid,1)
124                   DO  j = 1, mask_size_l(mid,2)
125                      DO  k = 1, mask_size_l(mid,3)
126                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
127                                   mask_j(mid,j),mask_i(mid,i))
128                      ENDDO
129                   ENDDO
130                ENDDO
131                resorted = .TRUE.
132             ELSE
133                CALL exchange_horiz( pc_av )
134                to_be_resorted => pc_av
135             ENDIF
136
137          CASE ( 'pr' )  ! mean particle radius
138             IF ( av == 0 )  THEN
139                DO  i = nxl, nxr
140                   DO  j = nys, nyn
141                      DO  k = nzb, nzt+1
142                         psi = prt_start_index(k,j,i)
143                         s_r3 = 0.0
144                         s_r4 = 0.0
145                         DO  n = psi, psi+prt_count(k,j,i)-1
146                            s_r3 = s_r3 + particles(n)%radius**3
147                            s_r4 = s_r4 + particles(n)%radius**4
148                         ENDDO
149                         IF ( s_r3 /= 0.0 )  THEN
150                            mean_r = s_r4 / s_r3
151                         ELSE
152                            mean_r = 0.0
153                         ENDIF
154                         tend(k,j,i) = mean_r
155                      ENDDO
156                   ENDDO
157                ENDDO
158                CALL exchange_horiz( tend )
159                DO  i = 1, mask_size_l(mid,1)
160                   DO  j = 1, mask_size_l(mid,2)
161                      DO  k = 1, mask_size_l(mid,3)
162                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
163                                   mask_j(mid,j),mask_i(mid,i))
164                      ENDDO
165                   ENDDO
166                ENDDO
167                resorted = .TRUE.
168             ELSE
169                CALL exchange_horiz( pr_av )
170                to_be_resorted => pr_av
171             ENDIF
172
173          CASE ( 'pt' )
174             IF ( av == 0 )  THEN
175                IF ( .NOT. cloud_physics ) THEN
176                   to_be_resorted => pt
177                ELSE
178                   DO  i = 1, mask_size_l(mid,1)
179                      DO  j = 1, mask_size_l(mid,2)
180                         DO  k = 1, mask_size_l(mid,3)
181                            local_pf(i,j,k) =  &
182                                 pt(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) &
183                                 + l_d_cp * pt_d_t(mask_k(mid,k)) * &
184                                   ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
185                         ENDDO
186                      ENDDO
187                   ENDDO
188                   resorted = .TRUE.
189                ENDIF
190             ELSE
191                to_be_resorted => pt_av
192             ENDIF
193
194          CASE ( 'q' )
195             IF ( av == 0 )  THEN
196                to_be_resorted => q
197             ELSE
198                to_be_resorted => q_av
199             ENDIF
200             
201          CASE ( 'ql' )
202             IF ( av == 0 )  THEN
203                to_be_resorted => ql
204             ELSE
205                to_be_resorted => ql_av
206             ENDIF
207
208          CASE ( 'ql_c' )
209             IF ( av == 0 )  THEN
210                to_be_resorted => ql_c
211             ELSE
212                to_be_resorted => ql_c_av
213             ENDIF
214
215          CASE ( 'ql_v' )
216             IF ( av == 0 )  THEN
217                to_be_resorted => ql_v
218             ELSE
219                to_be_resorted => ql_v_av
220             ENDIF
221
222          CASE ( 'ql_vp' )
223             IF ( av == 0 )  THEN
224                to_be_resorted => ql_vp
225             ELSE
226                to_be_resorted => ql_vp_av
227             ENDIF
228
229          CASE ( 'qv' )
230             IF ( av == 0 )  THEN
231                DO  i = 1, mask_size_l(mid,1)
232                   DO  j = 1, mask_size_l(mid,2)
233                      DO  k = 1, mask_size_l(mid,3)
234                         local_pf(i,j,k) =  &
235                              q(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) -  &
236                              ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
237                      ENDDO
238                   ENDDO
239                ENDDO
240                resorted = .TRUE.
241             ELSE
242                to_be_resorted => qv_av
243             ENDIF
244
245          CASE ( 'rho' )
246             IF ( av == 0 )  THEN
247                to_be_resorted => rho
248             ELSE
249                to_be_resorted => rho_av
250             ENDIF
251             
252          CASE ( 's' )
253             IF ( av == 0 )  THEN
254                to_be_resorted => q
255             ELSE
256                to_be_resorted => s_av
257             ENDIF
258             
259          CASE ( 'sa' )
260             IF ( av == 0 )  THEN
261                to_be_resorted => sa
262             ELSE
263                to_be_resorted => sa_av
264             ENDIF
265             
266          CASE ( 'u' )
267             IF ( av == 0 )  THEN
268                to_be_resorted => u
269             ELSE
270                to_be_resorted => u_av
271             ENDIF
272
273          CASE ( 'v' )
274             IF ( av == 0 )  THEN
275                to_be_resorted => v
276             ELSE
277                to_be_resorted => v_av
278             ENDIF
279
280          CASE ( 'vpt' )
281             IF ( av == 0 )  THEN
282                to_be_resorted => vpt
283             ELSE
284                to_be_resorted => vpt_av
285             ENDIF
286
287          CASE ( 'w' )
288             IF ( av == 0 )  THEN
289                to_be_resorted => w
290             ELSE
291                to_be_resorted => w_av
292             ENDIF
293
294          CASE DEFAULT
295!
296!--          User defined quantity
297             CALL user_data_output_mask(av, domask(mid,av,if), found, local_pf )
298             resorted = .TRUE.
299
300             IF ( .NOT. found )  THEN
301                WRITE ( message_string, * ) 'no output available for: ', &
302                                            TRIM( domask(mid,av,if) )
303                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
304             ENDIF
305
306       END SELECT
307
308!
309!--    Resort the array to be output, if not done above
310       IF ( .NOT. resorted )  THEN
311          DO  i = 1, mask_size_l(mid,1)
312             DO  j = 1, mask_size_l(mid,2)
313                DO  k = 1, mask_size_l(mid,3)
314                   local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
315                                      mask_j(mid,j),mask_i(mid,i))
316                ENDDO
317             ENDDO
318          ENDDO
319       ENDIF
320
321!
322!--    I/O block. I/O methods are implemented
323!--    (1) for parallel execution
324!--     a. with NetCDF 4 parallel I/O-enabled library
325!--     b. with NetCDF 3 library
326!--    (2) for serial execution.
327!--    The choice of method depends on the correct setting of preprocessor
328!--    directives __parallel and __netcdf4 as well as on the parameter
329!--    netcdf_data_format.
330#if defined( __parallel )
331#if defined( __netcdf4 )
332       IF ( netcdf_data_format > 2 )  THEN
333!
334!--       (1) a. Parallel I/O using NetCDF 4 (not yet tested)
335          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
336               id_var_domask(mid,av,if),  &
337               local_pf,  &
338               start = (/ mask_start_l(mid,1), mask_start_l(mid,2),  &
339                          mask_start_l(mid,3), domask_time_count(mid,av) /),  &
340               count = (/ mask_size_l(mid,1), mask_size_l(mid,2),  &
341                          mask_size_l(mid,3), 1 /) )
342          CALL handle_netcdf_error( 'data_output_mask', 461 )
343       ELSE
344#endif
345!
346!--       (1) b. Conventional I/O only through PE0
347!--       PE0 receives partial arrays from all processors of the respective mask
348!--       and outputs them. Here a barrier has to be set, because otherwise
349!--       "-MPI- FATAL: Remote protocol queue full" may occur.
350          CALL MPI_BARRIER( comm2d, ierr )
351
352          ngp = mask_size_l(mid,1) * mask_size_l(mid,2) * mask_size_l(mid,3)
353          IF ( myid == 0 )  THEN
354!
355!--          Local array can be relocated directly.
356             total_pf( &
357               mask_start_l(mid,1):mask_start_l(mid,1)+mask_size_l(mid,1)-1, &
358               mask_start_l(mid,2):mask_start_l(mid,2)+mask_size_l(mid,2)-1, &
359               mask_start_l(mid,3):mask_start_l(mid,3)+mask_size_l(mid,3)-1 ) &
360               = local_pf
361!
362!--          Receive data from all other PEs.
363             DO  n = 1, numprocs-1
364!
365!--             Receive index limits first, then array.
366!--             Index limits are received in arbitrary order from the PEs.
367                CALL MPI_RECV( ind(1), 6, MPI_INTEGER, MPI_ANY_SOURCE, 0,  &
368                     comm2d, status, ierr )
369!
370!--             Not all PEs have data for the mask
371                IF ( ind(1) /= -9999 )  THEN
372                   ngp = ( ind(2)-ind(1)+1 ) * (ind(4)-ind(3)+1 ) *  &
373                         ( ind(6)-ind(5)+1 )
374                   sender = status(MPI_SOURCE)
375                   DEALLOCATE( local_pf )
376                   ALLOCATE(local_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)))
377                   CALL MPI_RECV( local_pf(ind(1),ind(3),ind(5)), ngp,  &
378                        MPI_REAL, sender, 1, comm2d, status, ierr )
379                   total_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)) &
380                        = local_pf
381                ENDIF
382             ENDDO
383
384             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
385                  id_var_domask(mid,av,if), total_pf, &
386                  start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
387                  count = (/ mask_size(mid,1), mask_size(mid,2), &
388                             mask_size(mid,3), 1 /) )
389             CALL handle_netcdf_error( 'data_output_mask', 462 )
390
391          ELSE
392!
393!--          If at least part of the mask resides on the PE, send the index
394!--          limits for the target array, otherwise send -9999 to PE0.
395             IF ( mask_size_l(mid,1) > 0 .AND.  mask_size_l(mid,2) > 0 .AND. &
396                  mask_size_l(mid,3) > 0  ) &
397                  THEN
398                ind(1) = mask_start_l(mid,1)
399                ind(2) = mask_start_l(mid,1) + mask_size_l(mid,1) - 1
400                ind(3) = mask_start_l(mid,2)
401                ind(4) = mask_start_l(mid,2) + mask_size_l(mid,2) - 1
402                ind(5) = mask_start_l(mid,3)
403                ind(6) = mask_start_l(mid,3) + mask_size_l(mid,3) - 1
404             ELSE
405                ind(1) = -9999; ind(2) = -9999
406                ind(3) = -9999; ind(4) = -9999
407                ind(5) = -9999; ind(6) = -9999
408             ENDIF
409             CALL MPI_SEND( ind(1), 6, MPI_INTEGER, 0, 0, comm2d, ierr )
410!
411!--          If applicable, send data to PE0.
412             IF ( ind(1) /= -9999 )  THEN
413                CALL MPI_SEND( local_pf(1,1,1), ngp, MPI_REAL, 0, 1, comm2d, &
414                     ierr )
415             ENDIF
416          ENDIF
417!
418!--       A barrier has to be set, because otherwise some PEs may proceed too
419!--       fast so that PE0 may receive wrong data on tag 0.
420          CALL MPI_BARRIER( comm2d, ierr )
421#if defined( __netcdf4 )
422       ENDIF
423#endif
424#else
425!
426!--    (2) For serial execution of PALM, the single processor (PE0) holds all
427!--    data and writes them directly to file.
428       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
429            id_var_domask(mid,av,if),       &
430            local_pf, &
431            start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
432            count = (/ mask_size_l(mid,1), mask_size_l(mid,2), &
433                       mask_size_l(mid,3), 1 /) )
434       CALL handle_netcdf_error( 'data_output_mask', 463 )
435#endif
436
437       if = if + 1
438    ENDDO
439
440!
441!-- Deallocate temporary arrays.
442    DEALLOCATE( local_pf )
443#if defined( __parallel )
444    IF ( myid == 0 )  THEN
445       DEALLOCATE( total_pf )
446    ENDIF
447#endif
448
449
450    CALL cpu_log (log_point(49),'data_output_mask','stop','nobarrier')
451#endif
452
453 END SUBROUTINE data_output_mask
Note: See TracBrowser for help on using the repository browser.