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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 19.3 KB
Line 
1 SUBROUTINE data_output_mask( av )
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_mask.f90 1320 2014-03-20 08:40:49Z raasch $
27!
28! 1318 2014-03-17 13:35:16Z raasch
29! barrier argument removed from cpu_log,
30! module interfaces removed
31!
32! 1092 2013-02-02 11:24:22Z raasch
33! unused variables removed
34!
35! 1036 2012-10-22 13:43:42Z raasch
36! code put under GPL (PALM 3.9)
37!
38! 1031 2012-10-19 14:35:30Z raasch
39! netCDF4 without parallel file support implemented
40!
41! 1007 2012-09-19 14:30:36Z franke
42! Bugfix: calculation of pr must depend on the particle weighting factor,
43! missing calculation of ql_vp added
44!
45! 410 2009-12-04 17:05:40Z letzel
46! Initial version
47!
48! Description:
49! ------------
50! Masked data output in netCDF format for current mask (current value of mid).
51!------------------------------------------------------------------------------!
52
53#if defined( __netcdf )
54    USE arrays_3d,                                                             &
55        ONLY:  e, p, pt, q, ql, ql_c, ql_v, rho, sa, tend, u, v, vpt, w
56   
57    USE averaging,                                                             &
58        ONLY:  e_av, lpt_av, p_av, pc_av, pr_av, pt_av, q_av, ql_av, ql_c_av,  &
59               ql_v_av, ql_vp_av, qv_av, rho_av, s_av, sa_av, u_av, v_av,      &
60               vpt_av, w_av 
61   
62    USE cloud_parameters,                                                      &
63        ONLY:  l_d_cp, pt_d_t
64   
65    USE control_parameters,                                                    &
66        ONLY:  cloud_physics, domask, domask_no, domask_time_count, mask_i,    &
67               mask_j, mask_k, mask_size, mask_size_l, mask_start_l,           &
68               max_masks, message_string, mid, netcdf_data_format,             &
69               netcdf_output, nz_do3d, simulated_time
70   
71    USE cpulog,                                                                &
72        ONLY:  cpu_log, log_point
73   
74    USE indices,                                                               &
75        ONLY:  nbgp, nxl, nxr, nyn, nys, nzb, nzt
76       
77    USE kinds
78   
79    USE netcdf
80   
81    USE netcdf_control
82   
83    USE particle_attributes,                                                   &
84        ONLY:  particles, prt_count, prt_start_index
85   
86    USE pegrid
87
88    IMPLICIT NONE
89
90    INTEGER(iwp) ::  av       !:
91    INTEGER(iwp) ::  ngp      !:
92    INTEGER(iwp) ::  i        !:
93    INTEGER(iwp) ::  if       !:
94    INTEGER(iwp) ::  j        !:
95    INTEGER(iwp) ::  k        !:
96    INTEGER(iwp) ::  n        !:
97    INTEGER(iwp) ::  psi      !:
98    INTEGER(iwp) ::  sender   !:
99    INTEGER(iwp) ::  ind(6)   !:
100   
101    LOGICAL ::  found         !:
102    LOGICAL ::  resorted      !:
103   
104    REAL(wp) ::  mean_r       !:
105    REAL(wp) ::  s_r3         !:
106    REAL(wp) ::  s_r4         !:
107   
108    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !:
109#if defined( __parallel )
110    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  total_pf    !:
111#endif
112    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !:
113
114!
115!-- Return, if nothing to output
116    IF ( domask_no(mid,av) == 0 )  RETURN
117
118    CALL cpu_log (log_point(49),'data_output_mask','start')
119
120!
121!-- Open output file.
122    IF ( netcdf_output  .AND.  ( myid == 0  .OR.  netcdf_data_format > 4 ) ) &
123    THEN
124       CALL check_open( 200+mid+av*max_masks )
125    ENDIF 
126
127!
128!-- Allocate total and local output arrays.
129#if defined( __parallel )
130    IF ( myid == 0 )  THEN
131       ALLOCATE( total_pf(mask_size(mid,1),mask_size(mid,2),mask_size(mid,3)) )
132    ENDIF
133#endif
134    ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
135                       mask_size_l(mid,3)) )
136
137!
138!-- Update the netCDF time axis.
139    domask_time_count(mid,av) = domask_time_count(mid,av) + 1
140    IF ( netcdf_output  .AND.  ( myid == 0  .OR.  netcdf_data_format > 4 ) ) &
141    THEN
142       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_time_mask(mid,av), &
143                               (/ simulated_time /),                          &
144                               start = (/ domask_time_count(mid,av) /),       &
145                               count = (/ 1 /) )
146       CALL handle_netcdf_error( 'data_output_mask', 460 )
147    ENDIF
148
149!
150!-- Loop over all variables to be written.
151    if = 1
152
153    DO  WHILE ( domask(mid,av,if)(1:1) /= ' ' )
154!
155!--    Reallocate local_pf on PE 0 since its shape changes during MPI exchange
156       IF ( netcdf_data_format < 5   .AND.  myid == 0  .AND.  if > 1 )  THEN
157          DEALLOCATE( local_pf )
158          ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
159                             mask_size_l(mid,3)) )
160       ENDIF
161!
162!--    Store the variable chosen.
163       resorted = .FALSE.
164       SELECT CASE ( TRIM( domask(mid,av,if) ) )
165
166          CASE ( 'e' )
167             IF ( av == 0 )  THEN
168                to_be_resorted => e
169             ELSE
170                to_be_resorted => e_av
171             ENDIF
172
173          CASE ( 'lpt' )
174             IF ( av == 0 )  THEN
175                to_be_resorted => pt
176             ELSE
177                to_be_resorted => lpt_av
178             ENDIF
179
180          CASE ( 'p' )
181             IF ( av == 0 )  THEN
182                to_be_resorted => p
183             ELSE
184                to_be_resorted => p_av
185             ENDIF
186
187          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
188             IF ( av == 0 )  THEN
189                tend = prt_count
190                CALL exchange_horiz( tend, nbgp )
191                DO  i = 1, mask_size_l(mid,1)
192                   DO  j = 1, mask_size_l(mid,2)
193                      DO  k = 1, mask_size_l(mid,3)
194                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
195                                   mask_j(mid,j),mask_i(mid,i))
196                      ENDDO
197                   ENDDO
198                ENDDO
199                resorted = .TRUE.
200             ELSE
201                CALL exchange_horiz( pc_av, nbgp )
202                to_be_resorted => pc_av
203             ENDIF
204
205          CASE ( 'pr' )  ! mean particle radius
206             IF ( av == 0 )  THEN
207                DO  i = nxl, nxr
208                   DO  j = nys, nyn
209                      DO  k = nzb, nzt+1
210                         psi = prt_start_index(k,j,i)
211                         s_r3 = 0.0
212                         s_r4 = 0.0
213                         DO  n = psi, psi+prt_count(k,j,i)-1
214                            s_r3 = s_r3 + particles(n)%radius**3 * &
215                                          particles(n)%weight_factor
216                            s_r4 = s_r4 + particles(n)%radius**4 * &
217                                          particles(n)%weight_factor
218                         ENDDO
219                         IF ( s_r3 /= 0.0 )  THEN
220                            mean_r = s_r4 / s_r3
221                         ELSE
222                            mean_r = 0.0
223                         ENDIF
224                         tend(k,j,i) = mean_r
225                      ENDDO
226                   ENDDO
227                ENDDO
228                CALL exchange_horiz( tend, nbgp )
229                DO  i = 1, mask_size_l(mid,1)
230                   DO  j = 1, mask_size_l(mid,2)
231                      DO  k = 1, mask_size_l(mid,3)
232                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
233                                   mask_j(mid,j),mask_i(mid,i))
234                      ENDDO
235                   ENDDO
236                ENDDO
237                resorted = .TRUE.
238             ELSE
239                CALL exchange_horiz( pr_av, nbgp )
240                to_be_resorted => pr_av
241             ENDIF
242
243          CASE ( 'pt' )
244             IF ( av == 0 )  THEN
245                IF ( .NOT. cloud_physics ) THEN
246                   to_be_resorted => pt
247                ELSE
248                   DO  i = 1, mask_size_l(mid,1)
249                      DO  j = 1, mask_size_l(mid,2)
250                         DO  k = 1, mask_size_l(mid,3)
251                            local_pf(i,j,k) =  &
252                                 pt(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) &
253                                 + l_d_cp * pt_d_t(mask_k(mid,k)) * &
254                                   ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
255                         ENDDO
256                      ENDDO
257                   ENDDO
258                   resorted = .TRUE.
259                ENDIF
260             ELSE
261                to_be_resorted => pt_av
262             ENDIF
263
264          CASE ( 'q' )
265             IF ( av == 0 )  THEN
266                to_be_resorted => q
267             ELSE
268                to_be_resorted => q_av
269             ENDIF
270
271          CASE ( 'ql' )
272             IF ( av == 0 )  THEN
273                to_be_resorted => ql
274             ELSE
275                to_be_resorted => ql_av
276             ENDIF
277
278          CASE ( 'ql_c' )
279             IF ( av == 0 )  THEN
280                to_be_resorted => ql_c
281             ELSE
282                to_be_resorted => ql_c_av
283             ENDIF
284
285          CASE ( 'ql_v' )
286             IF ( av == 0 )  THEN
287                to_be_resorted => ql_v
288             ELSE
289                to_be_resorted => ql_v_av
290             ENDIF
291
292          CASE ( 'ql_vp' )
293             IF ( av == 0 )  THEN
294                DO  i = nxl, nxr
295                   DO  j = nys, nyn
296                      DO  k = nzb, nz_do3d
297                         psi = prt_start_index(k,j,i)
298                         DO  n = psi, psi+prt_count(k,j,i)-1
299                            tend(k,j,i) = tend(k,j,i) + &
300                                          particles(n)%weight_factor / &
301                                          prt_count(k,j,i)
302                         ENDDO
303                      ENDDO
304                   ENDDO
305                ENDDO
306                CALL exchange_horiz( tend, nbgp )
307                DO  i = 1, mask_size_l(mid,1)
308                   DO  j = 1, mask_size_l(mid,2)
309                      DO  k = 1, mask_size_l(mid,3)
310                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
311                                   mask_j(mid,j),mask_i(mid,i))
312                      ENDDO
313                   ENDDO
314                ENDDO
315                resorted = .TRUE.
316             ELSE
317                CALL exchange_horiz( ql_vp_av, nbgp )
318                to_be_resorted => ql_vp_av
319             ENDIF
320
321          CASE ( 'qv' )
322             IF ( av == 0 )  THEN
323                DO  i = 1, mask_size_l(mid,1)
324                   DO  j = 1, mask_size_l(mid,2)
325                      DO  k = 1, mask_size_l(mid,3)
326                         local_pf(i,j,k) =  &
327                              q(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) -  &
328                              ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
329                      ENDDO
330                   ENDDO
331                ENDDO
332                resorted = .TRUE.
333             ELSE
334                to_be_resorted => qv_av
335             ENDIF
336
337          CASE ( 'rho' )
338             IF ( av == 0 )  THEN
339                to_be_resorted => rho
340             ELSE
341                to_be_resorted => rho_av
342             ENDIF
343
344          CASE ( 's' )
345             IF ( av == 0 )  THEN
346                to_be_resorted => q
347             ELSE
348                to_be_resorted => s_av
349             ENDIF
350
351          CASE ( 'sa' )
352             IF ( av == 0 )  THEN
353                to_be_resorted => sa
354             ELSE
355                to_be_resorted => sa_av
356             ENDIF
357
358          CASE ( 'u' )
359             IF ( av == 0 )  THEN
360                to_be_resorted => u
361             ELSE
362                to_be_resorted => u_av
363             ENDIF
364
365          CASE ( 'v' )
366             IF ( av == 0 )  THEN
367                to_be_resorted => v
368             ELSE
369                to_be_resorted => v_av
370             ENDIF
371
372          CASE ( 'vpt' )
373             IF ( av == 0 )  THEN
374                to_be_resorted => vpt
375             ELSE
376                to_be_resorted => vpt_av
377             ENDIF
378
379          CASE ( 'w' )
380             IF ( av == 0 )  THEN
381                to_be_resorted => w
382             ELSE
383                to_be_resorted => w_av
384             ENDIF
385
386          CASE DEFAULT
387!
388!--          User defined quantity
389             CALL user_data_output_mask(av, domask(mid,av,if), found, local_pf )
390             resorted = .TRUE.
391
392             IF ( .NOT. found )  THEN
393                WRITE ( message_string, * ) 'no output available for: ', &
394                                            TRIM( domask(mid,av,if) )
395                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
396             ENDIF
397
398       END SELECT
399
400!
401!--    Resort the array to be output, if not done above
402       IF ( .NOT. resorted )  THEN
403          DO  i = 1, mask_size_l(mid,1)
404             DO  j = 1, mask_size_l(mid,2)
405                DO  k = 1, mask_size_l(mid,3)
406                   local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
407                                      mask_j(mid,j),mask_i(mid,i))
408                ENDDO
409             ENDDO
410          ENDDO
411       ENDIF
412
413!
414!--    I/O block. I/O methods are implemented
415!--    (1) for parallel execution
416!--     a. with netCDF 4 parallel I/O-enabled library
417!--     b. with netCDF 3 library
418!--    (2) for serial execution.
419!--    The choice of method depends on the correct setting of preprocessor
420!--    directives __parallel and __netcdf4_parallel as well as on the parameter
421!--    netcdf_data_format.
422#if defined( __parallel )
423#if defined( __netcdf4_parallel )
424       IF ( netcdf_data_format > 4 )  THEN
425!
426!--       (1) a. Parallel I/O using netCDF 4 (not yet tested)
427          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
428               id_var_domask(mid,av,if),  &
429               local_pf,  &
430               start = (/ mask_start_l(mid,1), mask_start_l(mid,2),  &
431                          mask_start_l(mid,3), 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', 461 )
435       ELSE
436#endif
437!
438!--       (1) b. Conventional I/O only through PE0
439!--       PE0 receives partial arrays from all processors of the respective mask
440!--       and outputs them. Here a barrier has to be set, because otherwise
441!--       "-MPI- FATAL: Remote protocol queue full" may occur.
442          CALL MPI_BARRIER( comm2d, ierr )
443
444          ngp = mask_size_l(mid,1) * mask_size_l(mid,2) * mask_size_l(mid,3)
445          IF ( myid == 0 )  THEN
446!
447!--          Local array can be relocated directly.
448             total_pf( &
449               mask_start_l(mid,1):mask_start_l(mid,1)+mask_size_l(mid,1)-1, &
450               mask_start_l(mid,2):mask_start_l(mid,2)+mask_size_l(mid,2)-1, &
451               mask_start_l(mid,3):mask_start_l(mid,3)+mask_size_l(mid,3)-1 ) &
452               = local_pf
453!
454!--          Receive data from all other PEs.
455             DO  n = 1, numprocs-1
456!
457!--             Receive index limits first, then array.
458!--             Index limits are received in arbitrary order from the PEs.
459                CALL MPI_RECV( ind(1), 6, MPI_INTEGER, MPI_ANY_SOURCE, 0,  &
460                     comm2d, status, ierr )
461!
462!--             Not all PEs have data for the mask
463                IF ( ind(1) /= -9999 )  THEN
464                   ngp = ( ind(2)-ind(1)+1 ) * (ind(4)-ind(3)+1 ) *  &
465                         ( ind(6)-ind(5)+1 )
466                   sender = status(MPI_SOURCE)
467                   DEALLOCATE( local_pf )
468                   ALLOCATE(local_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)))
469                   CALL MPI_RECV( local_pf(ind(1),ind(3),ind(5)), ngp,  &
470                        MPI_REAL, sender, 1, comm2d, status, ierr )
471                   total_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)) &
472                        = local_pf
473                ENDIF
474             ENDDO
475
476             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
477                  id_var_domask(mid,av,if), total_pf, &
478                  start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
479                  count = (/ mask_size(mid,1), mask_size(mid,2), &
480                             mask_size(mid,3), 1 /) )
481             CALL handle_netcdf_error( 'data_output_mask', 462 )
482
483          ELSE
484!
485!--          If at least part of the mask resides on the PE, send the index
486!--          limits for the target array, otherwise send -9999 to PE0.
487             IF ( mask_size_l(mid,1) > 0 .AND.  mask_size_l(mid,2) > 0 .AND. &
488                  mask_size_l(mid,3) > 0  ) &
489                  THEN
490                ind(1) = mask_start_l(mid,1)
491                ind(2) = mask_start_l(mid,1) + mask_size_l(mid,1) - 1
492                ind(3) = mask_start_l(mid,2)
493                ind(4) = mask_start_l(mid,2) + mask_size_l(mid,2) - 1
494                ind(5) = mask_start_l(mid,3)
495                ind(6) = mask_start_l(mid,3) + mask_size_l(mid,3) - 1
496             ELSE
497                ind(1) = -9999; ind(2) = -9999
498                ind(3) = -9999; ind(4) = -9999
499                ind(5) = -9999; ind(6) = -9999
500             ENDIF
501             CALL MPI_SEND( ind(1), 6, MPI_INTEGER, 0, 0, comm2d, ierr )
502!
503!--          If applicable, send data to PE0.
504             IF ( ind(1) /= -9999 )  THEN
505                CALL MPI_SEND( local_pf(1,1,1), ngp, MPI_REAL, 0, 1, comm2d, &
506                     ierr )
507             ENDIF
508          ENDIF
509!
510!--       A barrier has to be set, because otherwise some PEs may proceed too
511!--       fast so that PE0 may receive wrong data on tag 0.
512          CALL MPI_BARRIER( comm2d, ierr )
513#if defined( __netcdf4_parallel )
514       ENDIF
515#endif
516#else
517!
518!--    (2) For serial execution of PALM, the single processor (PE0) holds all
519!--    data and writes them directly to file.
520       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
521            id_var_domask(mid,av,if),       &
522            local_pf, &
523            start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
524            count = (/ mask_size_l(mid,1), mask_size_l(mid,2), &
525                       mask_size_l(mid,3), 1 /) )
526       CALL handle_netcdf_error( 'data_output_mask', 463 )
527#endif
528
529       if = if + 1
530
531    ENDDO
532
533!
534!-- Deallocate temporary arrays.
535    DEALLOCATE( local_pf )
536#if defined( __parallel )
537    IF ( myid == 0 )  THEN
538       DEALLOCATE( total_pf )
539    ENDIF
540#endif
541
542
543    CALL cpu_log( log_point(49), 'data_output_mask', 'stop' )
544#endif
545
546 END SUBROUTINE data_output_mask
Note: See TracBrowser for help on using the repository browser.