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

Last change on this file since 4039 was 4039, checked in by suehring, 5 years ago

diagnostic output: Modularize diagnostic output, rename subroutines; formatting adjustments; allocate arrays only when required; add output of uu, vv, ww to enable variance calculation via temporal EC method; radiation: bugfix in masked data output; flow_statistics: Correct conversion to kinematic vertical scalar fluxes in case of pw-scheme and statistic regions

  • Property svn:keywords set to Id
File size: 33.9 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-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_mask.f90 4039 2019-06-18 10:32:41Z suehring $
27! Modularize diagnostic output
28!
29! 3994 2019-05-22 18:08:09Z suehring
30! output of turbulence intensity added
31!
32! 3665 2019-01-10 08:28:24Z raasch
33! unused variables removed
34!
35! 3655 2019-01-07 16:51:22Z knoop
36! Fix output time levels (use time_since_reference_point)
37!
38! 3589 2018-11-30 15:09:51Z suehring
39! Move the control parameter "salsa" from salsa_mod.f90 to control_parameters
40!
41! 3582 2018-11-29 19:16:36Z suehring
42! add variable description
43!
44! 3467 2018-10-30 19:05:21Z suehring
45! Implementation of a new aerosol module salsa.
46!
47! 3435 2018-10-26 18:25:44Z gronemeier
48! Add terrain-following output
49!
50! 3421 2018-10-24 18:39:32Z gronemeier
51! Renamed output variables
52!
53! 3419 2018-10-24 17:27:31Z gronemeier
54! Minor formatting (kanani)
55! Call for chem_data_output_mask added (basit)
56!
57! 3274 2018-09-24 15:42:55Z knoop
58! Modularization of all bulk cloud physics code components
59!
60! 3241 2018-09-12 15:02:00Z raasch
61! unused variable removed
62!
63! 3083 2018-06-19 14:03:12Z gronemeier
64!
65!
66! 3045 2018-05-28 07:55:41Z Giersch
67! Error messages revised
68!
69! 3030 2018-05-23 14:37:00Z raasch
70! variable if renamed ivar
71!
72! 2718 2018-01-02 08:49:38Z maronga
73! Corrected "Former revisions" section
74!
75! 2696 2017-12-14 17:12:51Z kanani
76! Change in file header (GPL part)
77!
78! 2292 2017-06-20 09:51:42Z schwenkel
79! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
80! includes two more prognostic equations for cloud drop concentration (nc) 
81! and cloud water content (qc).
82!
83! 2101 2017-01-05 16:42:31Z suehring
84!
85! 2031 2016-10-21 15:11:58Z knoop
86! renamed variable rho to rho_ocean and rho_av to rho_ocean_av
87!
88! 2000 2016-08-20 18:09:15Z knoop
89! Forced header and separation lines into 80 columns
90!
91! 1980 2016-07-29 15:51:57Z suehring
92! Bugfix, in order to steer user-defined output, setting flag found explicitly
93! to .F.
94!
95! 1976 2016-07-27 13:28:04Z maronga
96! Output of radiation quantities is now done directly in the respective module
97!
98! 1960 2016-07-12 16:34:24Z suehring
99! Separate humidity and passive scalar
100!
101! 2016-03-06 18:36:17Z raasch
102! name change of netcdf routines and module + related changes,
103! switch back of netcdf data format moved from time integration routine to here
104!
105! 1691 2015-10-26 16:17:44Z maronga
106! Added output of radiative heating rates for RRTMG
107!
108! 1682 2015-10-07 23:56:08Z knoop
109! Code annotations made doxygen readable
110!
111! 1585 2015-04-30 07:05:52Z maronga
112! Added support for RRTMG
113!
114! 1438 2014-07-22 14:14:06Z heinze
115! +nr, qc, qr
116!
117! 1359 2014-04-11 17:15:14Z hoffmann
118! New particle structure integrated.
119!
120! 1353 2014-04-08 15:21:23Z heinze
121! REAL constants provided with KIND-attribute
122!
123! 1327 2014-03-21 11:00:16Z raasch
124!
125!
126! 1320 2014-03-20 08:40:49Z raasch
127! ONLY-attribute added to USE-statements,
128! kind-parameters added to all INTEGER and REAL declaration statements,
129! kinds are defined in new module kinds,
130! revision history before 2012 removed,
131! comment fields (!:) to be used for variable explanations added to
132! all variable declaration statements
133!
134! 1318 2014-03-17 13:35:16Z raasch
135! barrier argument removed from cpu_log,
136! module interfaces removed
137!
138! 1092 2013-02-02 11:24:22Z raasch
139! unused variables removed
140!
141! 1036 2012-10-22 13:43:42Z raasch
142! code put under GPL (PALM 3.9)
143!
144! 1031 2012-10-19 14:35:30Z raasch
145! netCDF4 without parallel file support implemented
146!
147! 1007 2012-09-19 14:30:36Z franke
148! Bugfix: calculation of pr must depend on the particle weighting factor,
149! missing calculation of ql_vp added
150!
151! 410 2009-12-04 17:05:40Z letzel
152! Initial version
153!
154! Description:
155! ------------
156!> Masked data output in netCDF format for current mask (current value of mid).
157!------------------------------------------------------------------------------!
158 SUBROUTINE data_output_mask( av )
159
160 
161
162#if defined( __netcdf )
163    USE arrays_3d,                                                             &
164        ONLY:  e, nc, nr, p, pt, q, qc, ql, ql_c, ql_v, qr, rho_ocean, s, sa,  &
165               tend, u, v, vpt, w, d_exner
166
167    USE averaging,                                                             &
168        ONLY:  e_av, lpt_av, nc_av, nr_av, p_av, pc_av, pr_av, pt_av, q_av,    &
169               qc_av, ql_av, ql_c_av, ql_v_av, ql_vp_av, qv_av, qr_av,         &
170               rho_ocean_av, s_av, sa_av, u_av, v_av, vpt_av, w_av 
171
172    USE basic_constants_and_equations_mod,                                     &
173        ONLY:  lv_d_cp
174
175    USE chemistry_model_mod,                                                   &
176        ONLY:  chem_data_output_mask
177
178    USE control_parameters,                                                    &
179        ONLY:  air_chemistry, domask, domask_no, domask_time_count, mask_i,    &
180               mask_j, mask_k, mask_size, mask_size_l, mask_start_l,           &
181               mask_surface,                                                   &
182               max_masks, message_string, mid, nz_do3d, salsa,                 &
183               time_since_reference_point
184
185    USE diagnostic_output_quantities_mod,                                      & 
186        ONLY:  doq_output_mask
187               
188    USE cpulog,                                                                &
189        ONLY:  cpu_log, log_point
190
191    USE indices,                                                               &
192        ONLY:  nbgp, nxl, nxr, nyn, nys, nzb, nzt
193
194    USE kinds
195
196    USE bulk_cloud_model_mod,                                                  &
197        ONLY:  bulk_cloud_model
198   
199    USE NETCDF
200   
201    USE netcdf_interface,                                                      &
202        ONLY:  id_set_mask, id_var_domask, id_var_time_mask, nc_stat,          &
203               netcdf_data_format, netcdf_handle_error
204   
205    USE particle_attributes,                                                   &
206        ONLY:  grid_particles, number_of_particles, particles,                 &
207               particle_advection_start, prt_count
208   
209    USE pegrid
210
211    USE radiation_model_mod,                                                   &
212        ONLY:  radiation, radiation_data_output_mask
213
214    USE salsa_mod,                                                             &
215        ONLY:  salsa_data_output_mask     
216       
217    USE surface_mod,                                                           &
218        ONLY :  get_topography_top_index_ji
219
220    IMPLICIT NONE
221
222    CHARACTER(LEN=5) ::  grid !< flag to distinquish between staggered grids
223
224    INTEGER(iwp) ::  av                      !< flag for (non-)average output
225    INTEGER(iwp) ::  ngp                     !< number of grid points of an output slice
226    INTEGER(iwp) ::  i                       !< loop index
227    INTEGER(iwp) ::  ivar                    !< variable index
228    INTEGER(iwp) ::  j                       !< loop index
229    INTEGER(iwp) ::  k                       !< loop index
230    INTEGER(iwp) ::  kk                      !< vertical index
231    INTEGER(iwp) ::  n                       !< loop index
232    INTEGER(iwp) ::  netcdf_data_format_save !< value of netcdf_data_format
233    INTEGER(iwp) ::  sender                  !< PE id of sending PE
234    INTEGER(iwp) ::  topo_top_ind            !< k index of highest horizontal surface
235    INTEGER(iwp) ::  ind(6)                  !< index limits (lower/upper bounds) of array 'local_2d'
236
237    LOGICAL ::  found      !< true if output variable was found
238    LOGICAL ::  resorted   !< true if variable is resorted
239
240    REAL(wp) ::  mean_r    !< mean particle radius
241    REAL(wp) ::  s_r2      !< sum( particle-radius**2 )
242    REAL(wp) ::  s_r3      !< sum( particle-radius**3 )
243   
244    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !< output array
245#if defined( __parallel )
246    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  total_pf    !< collected output array
247#endif
248    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< points to array which shall be output
249
250!
251!-- Return, if nothing to output
252    IF ( domask_no(mid,av) == 0 )  RETURN
253
254    CALL cpu_log (log_point(49),'data_output_mask','start')
255
256!
257!-- Parallel netcdf output is not tested so far for masked data, hence
258!-- netcdf_data_format is switched back to non-paralell output.
259    netcdf_data_format_save = netcdf_data_format
260    IF ( netcdf_data_format == 5 ) netcdf_data_format = 3
261    IF ( netcdf_data_format == 6 ) netcdf_data_format = 4
262
263!
264!-- Open output file.
265    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
266       CALL check_open( 200+mid+av*max_masks )
267    ENDIF 
268
269!
270!-- Allocate total and local output arrays.
271#if defined( __parallel )
272    IF ( myid == 0 )  THEN
273       ALLOCATE( total_pf(mask_size(mid,1),mask_size(mid,2),mask_size(mid,3)) )
274    ENDIF
275#endif
276    ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
277                       mask_size_l(mid,3)) )
278
279!
280!-- Update the netCDF time axis.
281    domask_time_count(mid,av) = domask_time_count(mid,av) + 1
282    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
283       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_time_mask(mid,av), &
284                               (/ time_since_reference_point /),              &
285                               start = (/ domask_time_count(mid,av) /),       &
286                               count = (/ 1 /) )
287       CALL netcdf_handle_error( 'data_output_mask', 460 )
288    ENDIF
289
290!
291!-- Loop over all variables to be written.
292    ivar = 1
293
294    DO  WHILE ( domask(mid,av,ivar)(1:1) /= ' ' )
295!
296!--    Reallocate local_pf on PE 0 since its shape changes during MPI exchange
297       IF ( netcdf_data_format < 5   .AND.  myid == 0  .AND.  ivar > 1 )  THEN
298          DEALLOCATE( local_pf )
299          ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
300                             mask_size_l(mid,3)) )
301       ENDIF
302!
303!--    Set default grid for terrain-following output
304       grid = 's'
305!
306!--    Set flag to steer output of radiation, land-surface, or user-defined
307!--    quantities
308       found = .FALSE.
309!
310!--    Store the variable chosen.
311       resorted = .FALSE.
312       SELECT CASE ( TRIM( domask(mid,av,ivar) ) )
313
314          CASE ( 'e' )
315             IF ( av == 0 )  THEN
316                to_be_resorted => e
317             ELSE
318                to_be_resorted => e_av
319             ENDIF
320
321          CASE ( 'thetal' )
322             IF ( av == 0 )  THEN
323                to_be_resorted => pt
324             ELSE
325                to_be_resorted => lpt_av
326             ENDIF
327
328          CASE ( 'nc' )
329             IF ( av == 0 )  THEN
330                to_be_resorted => nc
331             ELSE
332                to_be_resorted => nc_av
333             ENDIF
334
335          CASE ( 'nr' )
336             IF ( av == 0 )  THEN
337                to_be_resorted => nr
338             ELSE
339                to_be_resorted => nr_av
340             ENDIF
341
342          CASE ( 'p' )
343             IF ( av == 0 )  THEN
344                to_be_resorted => p
345             ELSE
346                to_be_resorted => p_av
347             ENDIF
348
349          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
350             IF ( av == 0 )  THEN
351                tend = prt_count
352                CALL exchange_horiz( tend, nbgp )
353                IF ( .NOT. mask_surface(mid) )  THEN
354                   DO  i = 1, mask_size_l(mid,1)
355                      DO  j = 1, mask_size_l(mid,2)
356                         DO  k = 1, mask_size_l(mid,3)
357                            local_pf(i,j,k) =  tend(mask_k(mid,k), &
358                                      mask_j(mid,j),mask_i(mid,i))
359                         ENDDO
360                      ENDDO
361                   ENDDO
362                ELSE
363!
364!--                Terrain-following masked output
365                   DO  i = 1, mask_size_l(mid,1)
366                      DO  j = 1, mask_size_l(mid,2)
367!
368!--                      Get k index of highest horizontal surface
369                         topo_top_ind =  &
370                            get_topography_top_index_ji( mask_j(mid,j),  &
371                                                         mask_i(mid,i),  &
372                                                         grid )
373                         DO  k = 1, mask_size_l(mid,3)
374                            kk = MIN( topo_top_ind+mask_k(mid,k), nzt+1 )
375                            local_pf(i,j,k) =  &
376                               tend(kk,mask_j(mid,j),mask_i(mid,i))
377                         ENDDO
378                      ENDDO
379                   ENDDO
380                ENDIF
381                resorted = .TRUE.
382             ELSE
383                CALL exchange_horiz( pc_av, nbgp )
384                to_be_resorted => pc_av
385             ENDIF
386
387          CASE ( 'pr' )  ! mean particle radius (effective radius)
388             IF ( av == 0 )  THEN
389                IF ( time_since_reference_point >= particle_advection_start )  THEN
390                   DO  i = nxl, nxr
391                      DO  j = nys, nyn
392                         DO  k = nzb, nz_do3d
393                            number_of_particles = prt_count(k,j,i)
394                            IF (number_of_particles <= 0)  CYCLE
395                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
396                            s_r2 = 0.0_wp
397                            s_r3 = 0.0_wp
398                            DO  n = 1, number_of_particles
399                               IF ( particles(n)%particle_mask )  THEN
400                                  s_r2 = s_r2 + grid_particles(k,j,i)%particles(n)%radius**2 * &
401                                         grid_particles(k,j,i)%particles(n)%weight_factor
402                                  s_r3 = s_r3 + grid_particles(k,j,i)%particles(n)%radius**3 * &
403                                         grid_particles(k,j,i)%particles(n)%weight_factor
404                               ENDIF
405                            ENDDO
406                            IF ( s_r2 > 0.0_wp )  THEN
407                               mean_r = s_r3 / s_r2
408                            ELSE
409                               mean_r = 0.0_wp
410                            ENDIF
411                            tend(k,j,i) = mean_r
412                         ENDDO
413                      ENDDO
414                   ENDDO
415                   CALL exchange_horiz( tend, nbgp )
416                ELSE
417                   tend = 0.0_wp
418                ENDIF
419                IF ( .NOT. mask_surface(mid) )  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) =  tend(mask_k(mid,k), &
424                                      mask_j(mid,j),mask_i(mid,i))
425                         ENDDO
426                      ENDDO
427                   ENDDO
428                ELSE
429!
430!--                Terrain-following masked output
431                   DO  i = 1, mask_size_l(mid,1)
432                      DO  j = 1, mask_size_l(mid,2)
433!
434!--                      Get k index of highest horizontal surface
435                         topo_top_ind =  &
436                            get_topography_top_index_ji( mask_j(mid,j),  &
437                                                         mask_i(mid,i),  &
438                                                         grid )
439                         DO  k = 1, mask_size_l(mid,3)
440                            kk = MIN( topo_top_ind+mask_k(mid,k), nzt+1 )
441                            local_pf(i,j,k) =  &
442                               tend(kk,mask_j(mid,j),mask_i(mid,i))
443                         ENDDO
444                      ENDDO
445                   ENDDO
446                ENDIF
447                resorted = .TRUE.
448             ELSE
449                CALL exchange_horiz( pr_av, nbgp )
450                to_be_resorted => pr_av
451             ENDIF
452
453          CASE ( 'theta' )
454             IF ( av == 0 )  THEN
455                IF ( .NOT. bulk_cloud_model ) THEN
456                   to_be_resorted => pt
457                ELSE
458                   IF ( .NOT. mask_surface(mid) )  THEN
459                      DO  i = 1, mask_size_l(mid,1)
460                         DO  j = 1, mask_size_l(mid,2)
461                            DO  k = 1, mask_size_l(mid,3)
462                               local_pf(i,j,k) =  &
463                                  pt(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) &
464                                  + lv_d_cp * d_exner(mask_k(mid,k)) *          &
465                                    ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
466                            ENDDO
467                         ENDDO
468                      ENDDO
469                   ELSE
470!
471!--                   Terrain-following masked output
472                      DO  i = 1, mask_size_l(mid,1)
473                         DO  j = 1, mask_size_l(mid,2)
474!
475!--                         Get k index of highest horizontal surface
476                            topo_top_ind =  &
477                               get_topography_top_index_ji( mask_j(mid,j),  &
478                                                            mask_i(mid,i),  &
479                                                            grid )
480                            DO  k = 1, mask_size_l(mid,3)
481                               kk = MIN( topo_top_ind+mask_k(mid,k), nzt+1 )
482                               local_pf(i,j,k) =  &
483                                    pt(kk,mask_j(mid,j),mask_i(mid,i) ) &
484                                    + lv_d_cp * d_exner(kk) *           &
485                                      ql(kk,mask_j(mid,j),mask_i(mid,i))
486                            ENDDO
487                         ENDDO
488                      ENDDO
489                   ENDIF                   
490                   resorted = .TRUE.
491                ENDIF
492             ELSE
493                to_be_resorted => pt_av
494             ENDIF
495
496          CASE ( 'q' )
497             IF ( av == 0 )  THEN
498                to_be_resorted => q
499             ELSE
500                to_be_resorted => q_av
501             ENDIF
502
503          CASE ( 'qc' )
504             IF ( av == 0 )  THEN
505                to_be_resorted => qc
506             ELSE
507                to_be_resorted => qc_av
508             ENDIF
509
510          CASE ( 'ql' )
511             IF ( av == 0 )  THEN
512                to_be_resorted => ql
513             ELSE
514                to_be_resorted => ql_av
515             ENDIF
516
517          CASE ( 'ql_c' )
518             IF ( av == 0 )  THEN
519                to_be_resorted => ql_c
520             ELSE
521                to_be_resorted => ql_c_av
522             ENDIF
523
524          CASE ( 'ql_v' )
525             IF ( av == 0 )  THEN
526                to_be_resorted => ql_v
527             ELSE
528                to_be_resorted => ql_v_av
529             ENDIF
530
531          CASE ( 'ql_vp' )
532             IF ( av == 0 )  THEN
533                IF ( time_since_reference_point >= particle_advection_start )  THEN
534                   DO  i = nxl, nxr
535                      DO  j = nys, nyn
536                         DO  k = nzb, nz_do3d
537                            number_of_particles = prt_count(k,j,i)
538                            IF (number_of_particles <= 0)  CYCLE
539                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
540                            DO  n = 1, number_of_particles
541                               IF ( particles(n)%particle_mask )  THEN
542                                  tend(k,j,i) = tend(k,j,i) + &
543                                          particles(n)%weight_factor / &
544                                          prt_count(k,j,i)
545                               ENDIF
546                            ENDDO
547                         ENDDO
548                      ENDDO
549                   ENDDO
550                   CALL exchange_horiz( tend, nbgp )
551                ELSE
552                   tend = 0.0_wp
553                ENDIF
554                IF ( .NOT. mask_surface(mid) )  THEN
555                   DO  i = 1, mask_size_l(mid,1)
556                      DO  j = 1, mask_size_l(mid,2)
557                         DO  k = 1, mask_size_l(mid,3)
558                            local_pf(i,j,k) =  tend(mask_k(mid,k), &
559                                      mask_j(mid,j),mask_i(mid,i))
560                         ENDDO
561                      ENDDO
562                   ENDDO
563                ELSE
564!
565!--                Terrain-following masked output
566                   DO  i = 1, mask_size_l(mid,1)
567                      DO  j = 1, mask_size_l(mid,2)
568!
569!--                      Get k index of highest horizontal surface
570                         topo_top_ind =  &
571                            get_topography_top_index_ji( mask_j(mid,j),  &
572                                                         mask_i(mid,i),  &
573                                                         grid )
574                         DO  k = 1, mask_size_l(mid,3)
575                            kk = MIN( topo_top_ind+mask_k(mid,k), nzt+1 )
576                            local_pf(i,j,k) =  &
577                               tend(kk,mask_j(mid,j),mask_i(mid,i))
578                         ENDDO
579                      ENDDO
580                   ENDDO
581                ENDIF
582                resorted = .TRUE.
583             ELSE
584                CALL exchange_horiz( ql_vp_av, nbgp )
585                to_be_resorted => ql_vp_av
586             ENDIF
587
588          CASE ( 'qv' )
589             IF ( av == 0 )  THEN
590                IF ( .NOT. mask_surface(mid) )  THEN
591                   DO  i = 1, mask_size_l(mid,1)
592                      DO  j = 1, mask_size_l(mid,2)
593                         DO  k = 1, mask_size_l(mid,3)
594                            local_pf(i,j,k) =  &
595                                 q(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) -  &
596                                 ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
597                         ENDDO
598                      ENDDO
599                   ENDDO
600                ELSE
601!
602!--                Terrain-following masked output
603                   DO  i = 1, mask_size_l(mid,1)
604                      DO  j = 1, mask_size_l(mid,2)
605!
606!--                      Get k index of highest horizontal surface
607                         topo_top_ind =  &
608                            get_topography_top_index_ji( mask_j(mid,j),  &
609                                                         mask_i(mid,i),  &
610                                                         grid )
611                         DO  k = 1, mask_size_l(mid,3)
612                            kk = MIN( topo_top_ind+mask_k(mid,k), nzt+1 )
613                            local_pf(i,j,k) =  &
614                                 q(kk,mask_j(mid,j),mask_i(mid,i)) -  &
615                                 ql(kk,mask_j(mid,j),mask_i(mid,i))
616                         ENDDO
617                      ENDDO
618                   ENDDO
619                ENDIF
620                resorted = .TRUE.
621             ELSE
622                to_be_resorted => qv_av
623             ENDIF
624
625          CASE ( 'qr' )
626             IF ( av == 0 )  THEN
627                to_be_resorted => qr
628             ELSE
629                to_be_resorted => qr_av
630             ENDIF
631
632          CASE ( 'rho_sea_water' )
633             IF ( av == 0 )  THEN
634                to_be_resorted => rho_ocean
635             ELSE
636                to_be_resorted => rho_ocean_av
637             ENDIF
638
639          CASE ( 's' )
640             IF ( av == 0 )  THEN
641                to_be_resorted => s
642             ELSE
643                to_be_resorted => s_av
644             ENDIF
645
646          CASE ( 'sa' )
647             IF ( av == 0 )  THEN
648                to_be_resorted => sa
649             ELSE
650                to_be_resorted => sa_av
651             ENDIF
652
653          CASE ( 'u' )
654             IF ( av == 0 )  THEN
655                to_be_resorted => u
656             ELSE
657                to_be_resorted => u_av
658             ENDIF
659
660          CASE ( 'v' )
661             IF ( av == 0 )  THEN
662                to_be_resorted => v
663             ELSE
664                to_be_resorted => v_av
665             ENDIF
666
667          CASE ( 'thetav' )
668             IF ( av == 0 )  THEN
669                to_be_resorted => vpt
670             ELSE
671                to_be_resorted => vpt_av
672             ENDIF
673
674          CASE ( 'w' )
675             grid = 'w'
676             IF ( av == 0 )  THEN
677                to_be_resorted => w
678             ELSE
679                to_be_resorted => w_av
680             ENDIF
681
682          CASE DEFAULT
683
684!
685!--          Radiation quantity
686             IF ( radiation )  THEN
687                CALL radiation_data_output_mask(av, domask(mid,av,ivar), found,&
688                                                local_pf )
689             ENDIF
690
691             IF ( air_chemistry )  THEN
692                CALL chem_data_output_mask(av, domask(mid,av,ivar), found,     &
693                                           local_pf )
694             ENDIF
695!
696!--          Check for diagnostic quantities
697             CALL doq_output_mask( av, domask(mid,av,ivar), found, local_pf )
698!
699!--          SALSA quantities
700             IF (  salsa )  THEN
701                CALL salsa_data_output_mask( av, domask(mid,av,ivar), found,   &
702                                             local_pf )
703             ENDIF         
704!
705!--          User defined quantity
706             IF ( .NOT. found )  THEN
707                CALL user_data_output_mask(av, domask(mid,av,ivar), found,     &
708                                           local_pf )
709             ENDIF
710
711             resorted = .TRUE.
712
713             IF ( .NOT. found )  THEN
714                WRITE ( message_string, * ) 'no masked output available for: ',&
715                                            TRIM( domask(mid,av,ivar) )
716                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
717             ENDIF
718
719       END SELECT
720
721!
722!--    Resort the array to be output, if not done above
723       IF ( .NOT. resorted )  THEN
724          IF ( .NOT. mask_surface(mid) )  THEN
725!
726!--          Default masked output
727             DO  i = 1, mask_size_l(mid,1)
728                DO  j = 1, mask_size_l(mid,2)
729                   DO  k = 1, mask_size_l(mid,3)
730                      local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
731                                         mask_j(mid,j),mask_i(mid,i))
732                   ENDDO
733                ENDDO
734             ENDDO
735
736          ELSE
737!
738!--          Terrain-following masked output
739             DO  i = 1, mask_size_l(mid,1)
740                DO  j = 1, mask_size_l(mid,2)
741!
742!--                Get k index of highest horizontal surface
743                   topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), &
744                                                               mask_i(mid,i), &
745                                                               grid )
746!
747!--                Save output array
748                   DO  k = 1, mask_size_l(mid,3)
749                      local_pf(i,j,k) = to_be_resorted(                       &
750                                             MIN( topo_top_ind+mask_k(mid,k), &
751                                                  nzt+1 ),                    &
752                                             mask_j(mid,j),                   &
753                                             mask_i(mid,i)                     )
754                   ENDDO
755                ENDDO
756             ENDDO
757
758          ENDIF
759       ENDIF
760
761!
762!--    I/O block. I/O methods are implemented
763!--    (1) for parallel execution
764!--     a. with netCDF 4 parallel I/O-enabled library
765!--     b. with netCDF 3 library
766!--    (2) for serial execution.
767!--    The choice of method depends on the correct setting of preprocessor
768!--    directives __parallel and __netcdf4_parallel as well as on the parameter
769!--    netcdf_data_format.
770#if defined( __parallel )
771#if defined( __netcdf4_parallel )
772       IF ( netcdf_data_format > 4 )  THEN
773!
774!--       (1) a. Parallel I/O using netCDF 4 (not yet tested)
775          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                         &
776               id_var_domask(mid,av,ivar), local_pf,                           &
777               start = (/ mask_start_l(mid,1), mask_start_l(mid,2),            &
778                          mask_start_l(mid,3), domask_time_count(mid,av) /),   &
779               count = (/ mask_size_l(mid,1), mask_size_l(mid,2),              &
780                          mask_size_l(mid,3), 1 /) )
781          CALL netcdf_handle_error( 'data_output_mask', 461 )
782       ELSE
783#endif
784!
785!--       (1) b. Conventional I/O only through PE0
786!--       PE0 receives partial arrays from all processors of the respective mask
787!--       and outputs them. Here a barrier has to be set, because otherwise
788!--       "-MPI- FATAL: Remote protocol queue full" may occur.
789          CALL MPI_BARRIER( comm2d, ierr )
790
791          ngp = mask_size_l(mid,1) * mask_size_l(mid,2) * mask_size_l(mid,3)
792          IF ( myid == 0 )  THEN
793!
794!--          Local array can be relocated directly.
795             total_pf( &
796               mask_start_l(mid,1):mask_start_l(mid,1)+mask_size_l(mid,1)-1, &
797               mask_start_l(mid,2):mask_start_l(mid,2)+mask_size_l(mid,2)-1, &
798               mask_start_l(mid,3):mask_start_l(mid,3)+mask_size_l(mid,3)-1 ) &
799               = local_pf
800!
801!--          Receive data from all other PEs.
802             DO  n = 1, numprocs-1
803!
804!--             Receive index limits first, then array.
805!--             Index limits are received in arbitrary order from the PEs.
806                CALL MPI_RECV( ind(1), 6, MPI_INTEGER, MPI_ANY_SOURCE, 0,  &
807                     comm2d, status, ierr )
808!
809!--             Not all PEs have data for the mask
810                IF ( ind(1) /= -9999 )  THEN
811                   ngp = ( ind(2)-ind(1)+1 ) * (ind(4)-ind(3)+1 ) *  &
812                         ( ind(6)-ind(5)+1 )
813                   sender = status(MPI_SOURCE)
814                   DEALLOCATE( local_pf )
815                   ALLOCATE(local_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)))
816                   CALL MPI_RECV( local_pf(ind(1),ind(3),ind(5)), ngp,  &
817                        MPI_REAL, sender, 1, comm2d, status, ierr )
818                   total_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)) &
819                        = local_pf
820                ENDIF
821             ENDDO
822
823             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
824                  id_var_domask(mid,av,ivar), total_pf,                        &
825                  start = (/ 1, 1, 1, domask_time_count(mid,av) /),            &
826                  count = (/ mask_size(mid,1), mask_size(mid,2),               &
827                             mask_size(mid,3), 1 /) )
828             CALL netcdf_handle_error( 'data_output_mask', 462 )
829
830          ELSE
831!
832!--          If at least part of the mask resides on the PE, send the index
833!--          limits for the target array, otherwise send -9999 to PE0.
834             IF ( mask_size_l(mid,1) > 0 .AND.  mask_size_l(mid,2) > 0 .AND. &
835                  mask_size_l(mid,3) > 0  ) &
836                  THEN
837                ind(1) = mask_start_l(mid,1)
838                ind(2) = mask_start_l(mid,1) + mask_size_l(mid,1) - 1
839                ind(3) = mask_start_l(mid,2)
840                ind(4) = mask_start_l(mid,2) + mask_size_l(mid,2) - 1
841                ind(5) = mask_start_l(mid,3)
842                ind(6) = mask_start_l(mid,3) + mask_size_l(mid,3) - 1
843             ELSE
844                ind(1) = -9999; ind(2) = -9999
845                ind(3) = -9999; ind(4) = -9999
846                ind(5) = -9999; ind(6) = -9999
847             ENDIF
848             CALL MPI_SEND( ind(1), 6, MPI_INTEGER, 0, 0, comm2d, ierr )
849!
850!--          If applicable, send data to PE0.
851             IF ( ind(1) /= -9999 )  THEN
852                CALL MPI_SEND( local_pf(1,1,1), ngp, MPI_REAL, 0, 1, comm2d, &
853                     ierr )
854             ENDIF
855          ENDIF
856!
857!--       A barrier has to be set, because otherwise some PEs may proceed too
858!--       fast so that PE0 may receive wrong data on tag 0.
859          CALL MPI_BARRIER( comm2d, ierr )
860#if defined( __netcdf4_parallel )
861       ENDIF
862#endif
863#else
864!
865!--    (2) For serial execution of PALM, the single processor (PE0) holds all
866!--    data and writes them directly to file.
867       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                            &
868                               id_var_domask(mid,av,ivar), local_pf,           &
869                             start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
870                             count = (/ mask_size_l(mid,1), mask_size_l(mid,2),&
871                               mask_size_l(mid,3), 1 /) )
872       CALL netcdf_handle_error( 'data_output_mask', 463 )
873#endif
874
875       ivar = ivar + 1
876
877    ENDDO
878
879!
880!-- Deallocate temporary arrays.
881    DEALLOCATE( local_pf )
882#if defined( __parallel )
883    IF ( myid == 0 )  THEN
884       DEALLOCATE( total_pf )
885    ENDIF
886#endif
887
888!
889!-- Switch back to original format given by user (see beginning of this routine)
890    netcdf_data_format = netcdf_data_format_save
891
892    CALL cpu_log( log_point(49), 'data_output_mask', 'stop' )
893#endif
894
895
896 END SUBROUTINE data_output_mask
Note: See TracBrowser for help on using the repository browser.