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

Last change on this file since 2032 was 2032, checked in by knoop, 7 years ago

last commit documented

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