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

Last change on this file since 4481 was 4457, checked in by raasch, 4 years ago

ghost point exchange modularized, bugfix for wrong 2d-exchange

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