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

Last change on this file since 4751 was 4559, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

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