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

Last change on this file since 3041 was 3030, checked in by raasch, 6 years ago

variable if renamed ivar

  • Property svn:keywords set to Id
File size: 24.6 KB
Line 
1!> @file data_output_mask.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_mask.f90 3030 2018-05-23 14:37:00Z gronemeier $
27! variable if renamed ivar
28!
29! 2718 2018-01-02 08:49:38Z maronga
30! Corrected "Former revisions" section
31!
32! 2696 2017-12-14 17:12:51Z kanani
33! Change in file header (GPL part)
34!
35! 2292 2017-06-20 09:51:42Z schwenkel
36! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
37! includes two more prognostic equations for cloud drop concentration (nc) 
38! and cloud water content (qc).
39!
40! 2101 2017-01-05 16:42:31Z suehring
41!
42! 2031 2016-10-21 15:11:58Z knoop
43! renamed variable rho to rho_ocean and rho_av to rho_ocean_av
44!
45! 2000 2016-08-20 18:09:15Z knoop
46! Forced header and separation lines into 80 columns
47!
48! 1980 2016-07-29 15:51:57Z suehring
49! Bugfix, in order to steer user-defined output, setting flag found explicitly
50! to .F.
51!
52! 1976 2016-07-27 13:28:04Z maronga
53! Output of radiation quantities is now done directly in the respective module
54!
55! 1960 2016-07-12 16:34:24Z suehring
56! Separate humidity and passive scalar
57!
58! 2016-03-06 18:36:17Z raasch
59! name change of netcdf routines and module + related changes,
60! switch back of netcdf data format moved from time integration routine to here
61!
62! 1691 2015-10-26 16:17:44Z maronga
63! Added output of radiative heating rates for RRTMG
64!
65! 1682 2015-10-07 23:56:08Z knoop
66! Code annotations made doxygen readable
67!
68! 1585 2015-04-30 07:05:52Z maronga
69! Added support for RRTMG
70!
71! 1438 2014-07-22 14:14:06Z heinze
72! +nr, qc, qr
73!
74! 1359 2014-04-11 17:15:14Z hoffmann
75! New particle structure integrated.
76!
77! 1353 2014-04-08 15:21:23Z heinze
78! REAL constants provided with KIND-attribute
79!
80! 1327 2014-03-21 11:00:16Z raasch
81!
82!
83! 1320 2014-03-20 08:40:49Z raasch
84! ONLY-attribute added to USE-statements,
85! kind-parameters added to all INTEGER and REAL declaration statements,
86! kinds are defined in new module kinds,
87! revision history before 2012 removed,
88! comment fields (!:) to be used for variable explanations added to
89! all variable declaration statements
90!
91! 1318 2014-03-17 13:35:16Z raasch
92! barrier argument removed from cpu_log,
93! module interfaces removed
94!
95! 1092 2013-02-02 11:24:22Z raasch
96! unused variables removed
97!
98! 1036 2012-10-22 13:43:42Z raasch
99! code put under GPL (PALM 3.9)
100!
101! 1031 2012-10-19 14:35:30Z raasch
102! netCDF4 without parallel file support implemented
103!
104! 1007 2012-09-19 14:30:36Z franke
105! Bugfix: calculation of pr must depend on the particle weighting factor,
106! missing calculation of ql_vp added
107!
108! 410 2009-12-04 17:05:40Z letzel
109! Initial version
110!
111! Description:
112! ------------
113!> Masked data output in netCDF format for current mask (current value of mid).
114!------------------------------------------------------------------------------!
115 SUBROUTINE data_output_mask( av )
116
117 
118
119#if defined( __netcdf )
120    USE arrays_3d,                                                             &
121        ONLY:  e, nc, nr, p, pt, q, qc, ql, ql_c, ql_v, qr, rho_ocean, s, sa,  &
122               tend, u, v, vpt, w
123   
124    USE averaging,                                                             &
125        ONLY:  e_av, lpt_av, nc_av, nr_av, p_av, pc_av, pr_av, pt_av, q_av,    &
126               qc_av, ql_av, ql_c_av, ql_v_av, ql_vp_av, qv_av, qr_av,         &
127               rho_ocean_av, s_av, sa_av, u_av, v_av, vpt_av, w_av 
128   
129    USE cloud_parameters,                                                      &
130        ONLY:  l_d_cp, pt_d_t
131   
132    USE control_parameters,                                                    &
133        ONLY:  cloud_physics, domask, domask_no, domask_time_count, mask_i,    &
134               mask_j, mask_k, mask_size, mask_size_l, mask_start_l,           &
135               max_masks, message_string, mid, nz_do3d, simulated_time
136    USE cpulog,                                                                &
137        ONLY:  cpu_log, log_point
138
139    USE indices,                                                               &
140        ONLY:  nbgp, nxl, nxr, nyn, nys, nzb, nzt
141       
142    USE kinds
143   
144    USE NETCDF
145   
146    USE netcdf_interface,                                                      &
147        ONLY:  id_set_mask, id_var_domask, id_var_time_mask, nc_stat,          &
148               netcdf_data_format, netcdf_handle_error
149   
150    USE particle_attributes,                                                   &
151        ONLY:  grid_particles, number_of_particles, particles,                 &
152               particle_advection_start, prt_count
153   
154    USE pegrid
155
156    USE radiation_model_mod,                                                   &
157        ONLY:  radiation, radiation_data_output_mask
158
159    IMPLICIT NONE
160
161    INTEGER(iwp) ::  av       !<
162    INTEGER(iwp) ::  ngp      !<
163    INTEGER(iwp) ::  i        !<
164    INTEGER(iwp) ::  ivar     !<
165    INTEGER(iwp) ::  j        !<
166    INTEGER(iwp) ::  k        !<
167    INTEGER(iwp) ::  n        !<
168    INTEGER(iwp) ::  netcdf_data_format_save !<
169    INTEGER(iwp) ::  psi      !<
170    INTEGER(iwp) ::  sender   !<
171    INTEGER(iwp) ::  ind(6)   !<
172   
173    LOGICAL ::  found         !<
174    LOGICAL ::  resorted      !<
175   
176    REAL(wp) ::  mean_r       !<
177    REAL(wp) ::  s_r2         !<
178    REAL(wp) ::  s_r3         !<
179   
180    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !<
181#if defined( __parallel )
182    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  total_pf    !<
183#endif
184    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !<
185
186!
187!-- Return, if nothing to output
188    IF ( domask_no(mid,av) == 0 )  RETURN
189
190    CALL cpu_log (log_point(49),'data_output_mask','start')
191
192!
193!-- Parallel netcdf output is not tested so far for masked data, hence
194!-- netcdf_data_format is switched back to non-paralell output.
195    netcdf_data_format_save = netcdf_data_format
196    IF ( netcdf_data_format == 5 ) netcdf_data_format = 3
197    IF ( netcdf_data_format == 6 ) netcdf_data_format = 4
198
199!
200!-- Open output file.
201    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
202       CALL check_open( 200+mid+av*max_masks )
203    ENDIF 
204
205!
206!-- Allocate total and local output arrays.
207#if defined( __parallel )
208    IF ( myid == 0 )  THEN
209       ALLOCATE( total_pf(mask_size(mid,1),mask_size(mid,2),mask_size(mid,3)) )
210    ENDIF
211#endif
212    ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
213                       mask_size_l(mid,3)) )
214
215!
216!-- Update the netCDF time axis.
217    domask_time_count(mid,av) = domask_time_count(mid,av) + 1
218    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
219       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_time_mask(mid,av), &
220                               (/ simulated_time /),                          &
221                               start = (/ domask_time_count(mid,av) /),       &
222                               count = (/ 1 /) )
223       CALL netcdf_handle_error( 'data_output_mask', 460 )
224    ENDIF
225
226!
227!-- Loop over all variables to be written.
228    ivar = 1
229
230    DO  WHILE ( domask(mid,av,ivar)(1:1) /= ' ' )
231!
232!--    Reallocate local_pf on PE 0 since its shape changes during MPI exchange
233       IF ( netcdf_data_format < 5   .AND.  myid == 0  .AND.  ivar > 1 )  THEN
234          DEALLOCATE( local_pf )
235          ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
236                             mask_size_l(mid,3)) )
237       ENDIF
238!
239!--    Set flag to steer output of radiation, land-surface, or user-defined
240!--    quantities
241       found = .FALSE.
242!
243!--    Store the variable chosen.
244       resorted = .FALSE.
245       SELECT CASE ( TRIM( domask(mid,av,ivar) ) )
246
247          CASE ( 'e' )
248             IF ( av == 0 )  THEN
249                to_be_resorted => e
250             ELSE
251                to_be_resorted => e_av
252             ENDIF
253
254          CASE ( 'lpt' )
255             IF ( av == 0 )  THEN
256                to_be_resorted => pt
257             ELSE
258                to_be_resorted => lpt_av
259             ENDIF
260
261          CASE ( 'nc' )
262             IF ( av == 0 )  THEN
263                to_be_resorted => nc
264             ELSE
265                to_be_resorted => nc_av
266             ENDIF
267
268          CASE ( 'nr' )
269             IF ( av == 0 )  THEN
270                to_be_resorted => nr
271             ELSE
272                to_be_resorted => nr_av
273             ENDIF
274
275          CASE ( 'p' )
276             IF ( av == 0 )  THEN
277                to_be_resorted => p
278             ELSE
279                to_be_resorted => p_av
280             ENDIF
281
282          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
283             IF ( av == 0 )  THEN
284                tend = prt_count
285                CALL exchange_horiz( tend, nbgp )
286                DO  i = 1, mask_size_l(mid,1)
287                   DO  j = 1, mask_size_l(mid,2)
288                      DO  k = 1, mask_size_l(mid,3)
289                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
290                                   mask_j(mid,j),mask_i(mid,i))
291                      ENDDO
292                   ENDDO
293                ENDDO
294                resorted = .TRUE.
295             ELSE
296                CALL exchange_horiz( pc_av, nbgp )
297                to_be_resorted => pc_av
298             ENDIF
299
300          CASE ( 'pr' )  ! mean particle radius (effective radius)
301             IF ( av == 0 )  THEN
302                IF ( simulated_time >= particle_advection_start )  THEN
303                   DO  i = nxl, nxr
304                      DO  j = nys, nyn
305                         DO  k = nzb, nz_do3d
306                            number_of_particles = prt_count(k,j,i)
307                            IF (number_of_particles <= 0)  CYCLE
308                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
309                            s_r2 = 0.0_wp
310                            s_r3 = 0.0_wp
311                            DO  n = 1, number_of_particles
312                               IF ( particles(n)%particle_mask )  THEN
313                                  s_r2 = s_r2 + grid_particles(k,j,i)%particles(n)%radius**2 * &
314                                         grid_particles(k,j,i)%particles(n)%weight_factor
315                                  s_r3 = s_r3 + grid_particles(k,j,i)%particles(n)%radius**3 * &
316                                         grid_particles(k,j,i)%particles(n)%weight_factor
317                               ENDIF
318                            ENDDO
319                            IF ( s_r2 > 0.0_wp )  THEN
320                               mean_r = s_r3 / s_r2
321                            ELSE
322                               mean_r = 0.0_wp
323                            ENDIF
324                            tend(k,j,i) = mean_r
325                         ENDDO
326                      ENDDO
327                   ENDDO
328                   CALL exchange_horiz( tend, nbgp )
329                ELSE
330                   tend = 0.0_wp
331                ENDIF
332                DO  i = 1, mask_size_l(mid,1)
333                   DO  j = 1, mask_size_l(mid,2)
334                      DO  k = 1, mask_size_l(mid,3)
335                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
336                                   mask_j(mid,j),mask_i(mid,i))
337                      ENDDO
338                   ENDDO
339                ENDDO
340                resorted = .TRUE.
341             ELSE
342                CALL exchange_horiz( pr_av, nbgp )
343                to_be_resorted => pr_av
344             ENDIF
345
346          CASE ( 'pt' )
347             IF ( av == 0 )  THEN
348                IF ( .NOT. cloud_physics ) THEN
349                   to_be_resorted => pt
350                ELSE
351                   DO  i = 1, mask_size_l(mid,1)
352                      DO  j = 1, mask_size_l(mid,2)
353                         DO  k = 1, mask_size_l(mid,3)
354                            local_pf(i,j,k) =  &
355                                 pt(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) &
356                                 + l_d_cp * pt_d_t(mask_k(mid,k)) * &
357                                   ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
358                         ENDDO
359                      ENDDO
360                   ENDDO
361                   resorted = .TRUE.
362                ENDIF
363             ELSE
364                to_be_resorted => pt_av
365             ENDIF
366
367          CASE ( 'q' )
368             IF ( av == 0 )  THEN
369                to_be_resorted => q
370             ELSE
371                to_be_resorted => q_av
372             ENDIF
373
374          CASE ( 'qc' )
375             IF ( av == 0 )  THEN
376                to_be_resorted => qc
377             ELSE
378                to_be_resorted => qc_av
379             ENDIF
380
381          CASE ( 'ql' )
382             IF ( av == 0 )  THEN
383                to_be_resorted => ql
384             ELSE
385                to_be_resorted => ql_av
386             ENDIF
387
388          CASE ( 'ql_c' )
389             IF ( av == 0 )  THEN
390                to_be_resorted => ql_c
391             ELSE
392                to_be_resorted => ql_c_av
393             ENDIF
394
395          CASE ( 'ql_v' )
396             IF ( av == 0 )  THEN
397                to_be_resorted => ql_v
398             ELSE
399                to_be_resorted => ql_v_av
400             ENDIF
401
402          CASE ( 'ql_vp' )
403             IF ( av == 0 )  THEN
404                IF ( simulated_time >= particle_advection_start )  THEN
405                   DO  i = nxl, nxr
406                      DO  j = nys, nyn
407                         DO  k = nzb, nz_do3d
408                            number_of_particles = prt_count(k,j,i)
409                            IF (number_of_particles <= 0)  CYCLE
410                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
411                            DO  n = 1, number_of_particles
412                               IF ( particles(n)%particle_mask )  THEN
413                                  tend(k,j,i) = tend(k,j,i) + &
414                                          particles(n)%weight_factor / &
415                                          prt_count(k,j,i)
416                               ENDIF
417                            ENDDO
418                         ENDDO
419                      ENDDO
420                   ENDDO
421                   CALL exchange_horiz( tend, nbgp )
422                ELSE
423                   tend = 0.0_wp
424                ENDIF
425                DO  i = 1, mask_size_l(mid,1)
426                   DO  j = 1, mask_size_l(mid,2)
427                      DO  k = 1, mask_size_l(mid,3)
428                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
429                                   mask_j(mid,j),mask_i(mid,i))
430                      ENDDO
431                   ENDDO
432                ENDDO
433                resorted = .TRUE.
434             ELSE
435                CALL exchange_horiz( ql_vp_av, nbgp )
436                to_be_resorted => ql_vp_av
437             ENDIF
438
439          CASE ( 'qv' )
440             IF ( av == 0 )  THEN
441                DO  i = 1, mask_size_l(mid,1)
442                   DO  j = 1, mask_size_l(mid,2)
443                      DO  k = 1, mask_size_l(mid,3)
444                         local_pf(i,j,k) =  &
445                              q(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) -  &
446                              ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
447                      ENDDO
448                   ENDDO
449                ENDDO
450                resorted = .TRUE.
451             ELSE
452                to_be_resorted => qv_av
453             ENDIF
454
455          CASE ( 'qr' )
456             IF ( av == 0 )  THEN
457                to_be_resorted => qr
458             ELSE
459                to_be_resorted => qr_av
460             ENDIF
461
462          CASE ( 'rho_ocean' )
463             IF ( av == 0 )  THEN
464                to_be_resorted => rho_ocean
465             ELSE
466                to_be_resorted => rho_ocean_av
467             ENDIF
468
469          CASE ( 's' )
470             IF ( av == 0 )  THEN
471                to_be_resorted => s
472             ELSE
473                to_be_resorted => s_av
474             ENDIF
475
476          CASE ( 'sa' )
477             IF ( av == 0 )  THEN
478                to_be_resorted => sa
479             ELSE
480                to_be_resorted => sa_av
481             ENDIF
482
483          CASE ( 'u' )
484             IF ( av == 0 )  THEN
485                to_be_resorted => u
486             ELSE
487                to_be_resorted => u_av
488             ENDIF
489
490          CASE ( 'v' )
491             IF ( av == 0 )  THEN
492                to_be_resorted => v
493             ELSE
494                to_be_resorted => v_av
495             ENDIF
496
497          CASE ( 'vpt' )
498             IF ( av == 0 )  THEN
499                to_be_resorted => vpt
500             ELSE
501                to_be_resorted => vpt_av
502             ENDIF
503
504          CASE ( 'w' )
505             IF ( av == 0 )  THEN
506                to_be_resorted => w
507             ELSE
508                to_be_resorted => w_av
509             ENDIF
510
511          CASE DEFAULT
512
513!
514!--          Radiation quantity
515             IF ( radiation )  THEN
516                CALL radiation_data_output_mask(av, domask(mid,av,ivar), found,&
517                                                local_pf )
518             ENDIF
519
520!
521!--          User defined quantity
522             IF ( .NOT. found )  THEN
523                CALL user_data_output_mask(av, domask(mid,av,ivar), found,     &
524                                           local_pf )
525             ENDIF
526
527             resorted = .TRUE.
528
529             IF ( .NOT. found )  THEN
530                WRITE ( message_string, * ) 'no output available for: ', &
531                                            TRIM( domask(mid,av,ivar) )
532                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
533             ENDIF
534
535       END SELECT
536
537!
538!--    Resort the array to be output, if not done above
539       IF ( .NOT. resorted )  THEN
540          DO  i = 1, mask_size_l(mid,1)
541             DO  j = 1, mask_size_l(mid,2)
542                DO  k = 1, mask_size_l(mid,3)
543                   local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
544                                      mask_j(mid,j),mask_i(mid,i))
545                ENDDO
546             ENDDO
547          ENDDO
548       ENDIF
549
550!
551!--    I/O block. I/O methods are implemented
552!--    (1) for parallel execution
553!--     a. with netCDF 4 parallel I/O-enabled library
554!--     b. with netCDF 3 library
555!--    (2) for serial execution.
556!--    The choice of method depends on the correct setting of preprocessor
557!--    directives __parallel and __netcdf4_parallel as well as on the parameter
558!--    netcdf_data_format.
559#if defined( __parallel )
560#if defined( __netcdf4_parallel )
561       IF ( netcdf_data_format > 4 )  THEN
562!
563!--       (1) a. Parallel I/O using netCDF 4 (not yet tested)
564          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                         &
565               id_var_domask(mid,av,ivar), local_pf,                           &
566               start = (/ mask_start_l(mid,1), mask_start_l(mid,2),            &
567                          mask_start_l(mid,3), domask_time_count(mid,av) /),   &
568               count = (/ mask_size_l(mid,1), mask_size_l(mid,2),              &
569                          mask_size_l(mid,3), 1 /) )
570          CALL netcdf_handle_error( 'data_output_mask', 461 )
571       ELSE
572#endif
573!
574!--       (1) b. Conventional I/O only through PE0
575!--       PE0 receives partial arrays from all processors of the respective mask
576!--       and outputs them. Here a barrier has to be set, because otherwise
577!--       "-MPI- FATAL: Remote protocol queue full" may occur.
578          CALL MPI_BARRIER( comm2d, ierr )
579
580          ngp = mask_size_l(mid,1) * mask_size_l(mid,2) * mask_size_l(mid,3)
581          IF ( myid == 0 )  THEN
582!
583!--          Local array can be relocated directly.
584             total_pf( &
585               mask_start_l(mid,1):mask_start_l(mid,1)+mask_size_l(mid,1)-1, &
586               mask_start_l(mid,2):mask_start_l(mid,2)+mask_size_l(mid,2)-1, &
587               mask_start_l(mid,3):mask_start_l(mid,3)+mask_size_l(mid,3)-1 ) &
588               = local_pf
589!
590!--          Receive data from all other PEs.
591             DO  n = 1, numprocs-1
592!
593!--             Receive index limits first, then array.
594!--             Index limits are received in arbitrary order from the PEs.
595                CALL MPI_RECV( ind(1), 6, MPI_INTEGER, MPI_ANY_SOURCE, 0,  &
596                     comm2d, status, ierr )
597!
598!--             Not all PEs have data for the mask
599                IF ( ind(1) /= -9999 )  THEN
600                   ngp = ( ind(2)-ind(1)+1 ) * (ind(4)-ind(3)+1 ) *  &
601                         ( ind(6)-ind(5)+1 )
602                   sender = status(MPI_SOURCE)
603                   DEALLOCATE( local_pf )
604                   ALLOCATE(local_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)))
605                   CALL MPI_RECV( local_pf(ind(1),ind(3),ind(5)), ngp,  &
606                        MPI_REAL, sender, 1, comm2d, status, ierr )
607                   total_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)) &
608                        = local_pf
609                ENDIF
610             ENDDO
611
612             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
613                  id_var_domask(mid,av,ivar), total_pf,                        &
614                  start = (/ 1, 1, 1, domask_time_count(mid,av) /),            &
615                  count = (/ mask_size(mid,1), mask_size(mid,2),               &
616                             mask_size(mid,3), 1 /) )
617             CALL netcdf_handle_error( 'data_output_mask', 462 )
618
619          ELSE
620!
621!--          If at least part of the mask resides on the PE, send the index
622!--          limits for the target array, otherwise send -9999 to PE0.
623             IF ( mask_size_l(mid,1) > 0 .AND.  mask_size_l(mid,2) > 0 .AND. &
624                  mask_size_l(mid,3) > 0  ) &
625                  THEN
626                ind(1) = mask_start_l(mid,1)
627                ind(2) = mask_start_l(mid,1) + mask_size_l(mid,1) - 1
628                ind(3) = mask_start_l(mid,2)
629                ind(4) = mask_start_l(mid,2) + mask_size_l(mid,2) - 1
630                ind(5) = mask_start_l(mid,3)
631                ind(6) = mask_start_l(mid,3) + mask_size_l(mid,3) - 1
632             ELSE
633                ind(1) = -9999; ind(2) = -9999
634                ind(3) = -9999; ind(4) = -9999
635                ind(5) = -9999; ind(6) = -9999
636             ENDIF
637             CALL MPI_SEND( ind(1), 6, MPI_INTEGER, 0, 0, comm2d, ierr )
638!
639!--          If applicable, send data to PE0.
640             IF ( ind(1) /= -9999 )  THEN
641                CALL MPI_SEND( local_pf(1,1,1), ngp, MPI_REAL, 0, 1, comm2d, &
642                     ierr )
643             ENDIF
644          ENDIF
645!
646!--       A barrier has to be set, because otherwise some PEs may proceed too
647!--       fast so that PE0 may receive wrong data on tag 0.
648          CALL MPI_BARRIER( comm2d, ierr )
649#if defined( __netcdf4_parallel )
650       ENDIF
651#endif
652#else
653!
654!--    (2) For serial execution of PALM, the single processor (PE0) holds all
655!--    data and writes them directly to file.
656       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                            &
657                               id_var_domask(mid,av,ivar), local_pf,           &
658                             start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
659                             count = (/ mask_size_l(mid,1), mask_size_l(mid,2),&
660                               mask_size_l(mid,3), 1 /) )
661       CALL netcdf_handle_error( 'data_output_mask', 463 )
662#endif
663
664       ivar = ivar + 1
665
666    ENDDO
667
668!
669!-- Deallocate temporary arrays.
670    DEALLOCATE( local_pf )
671#if defined( __parallel )
672    IF ( myid == 0 )  THEN
673       DEALLOCATE( total_pf )
674    ENDIF
675#endif
676
677!
678!-- Switch back to original format given by user (see beginning of this routine)
679    netcdf_data_format = netcdf_data_format_save
680
681    CALL cpu_log( log_point(49), 'data_output_mask', 'stop' )
682#endif
683
684 END SUBROUTINE data_output_mask
Note: See TracBrowser for help on using the repository browser.