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

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

Merge from branch resler: Changed behaviour of masked output over surface to follow terrain and ignore buildings

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