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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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