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

Last change on this file since 4331 was 4331, checked in by suehring, 4 years ago

New diagnostic output for 10-m wind speed; Diagnostic output of 2-m potential temperature moved to diagnostic output

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