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

Last change on this file since 3846 was 3665, checked in by raasch, 5 years ago

dummy statements added to avoid compiler warnings about unused variables, unused variables removed, ssh-call for submitting batch jobs on remote systems modified again to avoid output of login messages on specific systems

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