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

Last change on this file since 2292 was 2292, checked in by schwenkel, 7 years ago

implementation of new bulk microphysics scheme

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