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

Last change on this file since 4105 was 4069, checked in by Giersch, 5 years ago

Bugfix for masked output, compiler warning removed, test case for wind turbine model revised

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