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

Last change on this file since 4329 was 4329, checked in by motisi, 4 years ago

Renamed wall_flags_0 to wall_flags_static_0

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