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

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

new module for diagnostic output quantities added + output of turbulence intensity

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