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

Last change on this file since 3435 was 3435, checked in by gronemeier, 5 years ago

new: terrain-following masked output; bugfixes: increase vertical dimension of gamma_w_green_sat by 1, add checks for masked output for chemistry_model and radiation_model, reordered calls to xxx_define_netcdf_grid in masked output part

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