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

Last change on this file since 1360 was 1360, checked in by hoffmann, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 20.9 KB
Line 
1 SUBROUTINE data_output_mask( av )
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_mask.f90 1360 2014-04-11 17:20:32Z hoffmann $
27!
28! 1359 2014-04-11 17:15:14Z hoffmann
29! New particle structure integrated.
30!
31! 1353 2014-04-08 15:21:23Z heinze
32! REAL constants provided with KIND-attribute
33!
34! 1327 2014-03-21 11:00:16Z raasch
35!
36!
37! 1320 2014-03-20 08:40:49Z raasch
38! ONLY-attribute added to USE-statements,
39! kind-parameters added to all INTEGER and REAL declaration statements,
40! kinds are defined in new module kinds,
41! revision history before 2012 removed,
42! comment fields (!:) to be used for variable explanations added to
43! all variable declaration statements
44!
45! 1318 2014-03-17 13:35:16Z raasch
46! barrier argument removed from cpu_log,
47! module interfaces removed
48!
49! 1092 2013-02-02 11:24:22Z raasch
50! unused variables removed
51!
52! 1036 2012-10-22 13:43:42Z raasch
53! code put under GPL (PALM 3.9)
54!
55! 1031 2012-10-19 14:35:30Z raasch
56! netCDF4 without parallel file support implemented
57!
58! 1007 2012-09-19 14:30:36Z franke
59! Bugfix: calculation of pr must depend on the particle weighting factor,
60! missing calculation of ql_vp added
61!
62! 410 2009-12-04 17:05:40Z letzel
63! Initial version
64!
65! Description:
66! ------------
67! Masked data output in netCDF format for current mask (current value of mid).
68!------------------------------------------------------------------------------!
69
70#if defined( __netcdf )
71    USE arrays_3d,                                                             &
72        ONLY:  e, p, pt, q, ql, ql_c, ql_v, rho, sa, tend, u, v, vpt, w
73   
74    USE averaging,                                                             &
75        ONLY:  e_av, lpt_av, p_av, pc_av, pr_av, pt_av, q_av, ql_av, ql_c_av,  &
76               ql_v_av, ql_vp_av, qv_av, rho_av, s_av, sa_av, u_av, v_av,      &
77               vpt_av, w_av 
78   
79    USE cloud_parameters,                                                      &
80        ONLY:  l_d_cp, pt_d_t
81   
82    USE control_parameters,                                                    &
83        ONLY:  cloud_physics, domask, domask_no, domask_time_count, mask_i,    &
84               mask_j, mask_k, mask_size, mask_size_l, mask_start_l,           &
85               max_masks, message_string, mid, netcdf_data_format,             &
86               nz_do3d, simulated_time
87   
88    USE cpulog,                                                                &
89        ONLY:  cpu_log, log_point
90   
91    USE indices,                                                               &
92        ONLY:  nbgp, nxl, nxr, nyn, nys, nzb, nzt
93       
94    USE kinds
95   
96    USE netcdf
97   
98    USE netcdf_control
99   
100    USE particle_attributes,                                                   &
101        ONLY:  grid_particles, number_of_particles, particles,                 &
102               particle_advection_start, prt_count
103   
104    USE pegrid
105
106    IMPLICIT NONE
107
108    INTEGER(iwp) ::  av       !:
109    INTEGER(iwp) ::  ngp      !:
110    INTEGER(iwp) ::  i        !:
111    INTEGER(iwp) ::  if       !:
112    INTEGER(iwp) ::  j        !:
113    INTEGER(iwp) ::  k        !:
114    INTEGER(iwp) ::  n        !:
115    INTEGER(iwp) ::  psi      !:
116    INTEGER(iwp) ::  sender   !:
117    INTEGER(iwp) ::  ind(6)   !:
118   
119    LOGICAL ::  found         !:
120    LOGICAL ::  resorted      !:
121   
122    REAL(wp) ::  mean_r       !:
123    REAL(wp) ::  s_r2         !:
124    REAL(wp) ::  s_r3         !:
125   
126    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !:
127#if defined( __parallel )
128    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  total_pf    !:
129#endif
130    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !:
131
132!
133!-- Return, if nothing to output
134    IF ( domask_no(mid,av) == 0 )  RETURN
135
136    CALL cpu_log (log_point(49),'data_output_mask','start')
137
138!
139!-- Open output file.
140    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
141       CALL check_open( 200+mid+av*max_masks )
142    ENDIF 
143
144!
145!-- Allocate total and local output arrays.
146#if defined( __parallel )
147    IF ( myid == 0 )  THEN
148       ALLOCATE( total_pf(mask_size(mid,1),mask_size(mid,2),mask_size(mid,3)) )
149    ENDIF
150#endif
151    ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
152                       mask_size_l(mid,3)) )
153
154!
155!-- Update the netCDF time axis.
156    domask_time_count(mid,av) = domask_time_count(mid,av) + 1
157    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
158       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_time_mask(mid,av), &
159                               (/ simulated_time /),                          &
160                               start = (/ domask_time_count(mid,av) /),       &
161                               count = (/ 1 /) )
162       CALL handle_netcdf_error( 'data_output_mask', 460 )
163    ENDIF
164
165!
166!-- Loop over all variables to be written.
167    if = 1
168
169    DO  WHILE ( domask(mid,av,if)(1:1) /= ' ' )
170!
171!--    Reallocate local_pf on PE 0 since its shape changes during MPI exchange
172       IF ( netcdf_data_format < 5   .AND.  myid == 0  .AND.  if > 1 )  THEN
173          DEALLOCATE( local_pf )
174          ALLOCATE( local_pf(mask_size_l(mid,1),mask_size_l(mid,2), &
175                             mask_size_l(mid,3)) )
176       ENDIF
177!
178!--    Store the variable chosen.
179       resorted = .FALSE.
180       SELECT CASE ( TRIM( domask(mid,av,if) ) )
181
182          CASE ( 'e' )
183             IF ( av == 0 )  THEN
184                to_be_resorted => e
185             ELSE
186                to_be_resorted => e_av
187             ENDIF
188
189          CASE ( 'lpt' )
190             IF ( av == 0 )  THEN
191                to_be_resorted => pt
192             ELSE
193                to_be_resorted => lpt_av
194             ENDIF
195
196          CASE ( 'p' )
197             IF ( av == 0 )  THEN
198                to_be_resorted => p
199             ELSE
200                to_be_resorted => p_av
201             ENDIF
202
203          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
204             IF ( av == 0 )  THEN
205                tend = prt_count
206                CALL exchange_horiz( tend, nbgp )
207                DO  i = 1, mask_size_l(mid,1)
208                   DO  j = 1, mask_size_l(mid,2)
209                      DO  k = 1, mask_size_l(mid,3)
210                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
211                                   mask_j(mid,j),mask_i(mid,i))
212                      ENDDO
213                   ENDDO
214                ENDDO
215                resorted = .TRUE.
216             ELSE
217                CALL exchange_horiz( pc_av, nbgp )
218                to_be_resorted => pc_av
219             ENDIF
220
221          CASE ( 'pr' )  ! mean particle radius (effective radius)
222             IF ( av == 0 )  THEN
223                IF ( simulated_time >= particle_advection_start )  THEN
224                   DO  i = nxl, nxr
225                      DO  j = nys, nyn
226                         DO  k = nzb, nz_do3d
227                            number_of_particles = prt_count(k,j,i)
228                            IF (number_of_particles <= 0)  CYCLE
229                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
230                            s_r2 = 0.0_wp
231                            s_r3 = 0.0_wp
232                            DO  n = 1, number_of_particles
233                               IF ( particles(n)%particle_mask )  THEN
234                                  s_r2 = s_r2 + grid_particles(k,j,i)%particles(n)%radius**2 * &
235                                         grid_particles(k,j,i)%particles(n)%weight_factor
236                                  s_r3 = s_r3 + grid_particles(k,j,i)%particles(n)%radius**3 * &
237                                         grid_particles(k,j,i)%particles(n)%weight_factor
238                               ENDIF
239                            ENDDO
240                            IF ( s_r2 > 0.0_wp )  THEN
241                               mean_r = s_r3 / s_r2
242                            ELSE
243                               mean_r = 0.0_wp
244                            ENDIF
245                            tend(k,j,i) = mean_r
246                         ENDDO
247                      ENDDO
248                   ENDDO
249                   CALL exchange_horiz( tend, nbgp )
250                ELSE
251                   tend = 0.0_wp
252                ENDIF
253                DO  i = 1, mask_size_l(mid,1)
254                   DO  j = 1, mask_size_l(mid,2)
255                      DO  k = 1, mask_size_l(mid,3)
256                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
257                                   mask_j(mid,j),mask_i(mid,i))
258                      ENDDO
259                   ENDDO
260                ENDDO
261                resorted = .TRUE.
262             ELSE
263                CALL exchange_horiz( pr_av, nbgp )
264                to_be_resorted => pr_av
265             ENDIF
266
267          CASE ( 'pt' )
268             IF ( av == 0 )  THEN
269                IF ( .NOT. cloud_physics ) THEN
270                   to_be_resorted => pt
271                ELSE
272                   DO  i = 1, mask_size_l(mid,1)
273                      DO  j = 1, mask_size_l(mid,2)
274                         DO  k = 1, mask_size_l(mid,3)
275                            local_pf(i,j,k) =  &
276                                 pt(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) &
277                                 + l_d_cp * pt_d_t(mask_k(mid,k)) * &
278                                   ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
279                         ENDDO
280                      ENDDO
281                   ENDDO
282                   resorted = .TRUE.
283                ENDIF
284             ELSE
285                to_be_resorted => pt_av
286             ENDIF
287
288          CASE ( 'q' )
289             IF ( av == 0 )  THEN
290                to_be_resorted => q
291             ELSE
292                to_be_resorted => q_av
293             ENDIF
294
295          CASE ( 'ql' )
296             IF ( av == 0 )  THEN
297                to_be_resorted => ql
298             ELSE
299                to_be_resorted => ql_av
300             ENDIF
301
302          CASE ( 'ql_c' )
303             IF ( av == 0 )  THEN
304                to_be_resorted => ql_c
305             ELSE
306                to_be_resorted => ql_c_av
307             ENDIF
308
309          CASE ( 'ql_v' )
310             IF ( av == 0 )  THEN
311                to_be_resorted => ql_v
312             ELSE
313                to_be_resorted => ql_v_av
314             ENDIF
315
316          CASE ( 'ql_vp' )
317             IF ( av == 0 )  THEN
318                IF ( simulated_time >= particle_advection_start )  THEN
319                   DO  i = nxl, nxr
320                      DO  j = nys, nyn
321                         DO  k = nzb, nz_do3d
322                            number_of_particles = prt_count(k,j,i)
323                            IF (number_of_particles <= 0)  CYCLE
324                            particles => grid_particles(k,j,i)%particles(1:number_of_particles)
325                            DO  n = 1, number_of_particles
326                               IF ( particles(n)%particle_mask )  THEN
327                                  tend(k,j,i) = tend(k,j,i) + &
328                                          particles(n)%weight_factor / &
329                                          prt_count(k,j,i)
330                               ENDIF
331                            ENDDO
332                         ENDDO
333                      ENDDO
334                   ENDDO
335                   CALL exchange_horiz( tend, nbgp )
336                ELSE
337                   tend = 0.0_wp
338                ENDIF
339                DO  i = 1, mask_size_l(mid,1)
340                   DO  j = 1, mask_size_l(mid,2)
341                      DO  k = 1, mask_size_l(mid,3)
342                         local_pf(i,j,k) =  tend(mask_k(mid,k), &
343                                   mask_j(mid,j),mask_i(mid,i))
344                      ENDDO
345                   ENDDO
346                ENDDO
347                resorted = .TRUE.
348             ELSE
349                CALL exchange_horiz( ql_vp_av, nbgp )
350                to_be_resorted => ql_vp_av
351             ENDIF
352
353          CASE ( 'qv' )
354             IF ( av == 0 )  THEN
355                DO  i = 1, mask_size_l(mid,1)
356                   DO  j = 1, mask_size_l(mid,2)
357                      DO  k = 1, mask_size_l(mid,3)
358                         local_pf(i,j,k) =  &
359                              q(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i)) -  &
360                              ql(mask_k(mid,k),mask_j(mid,j),mask_i(mid,i))
361                      ENDDO
362                   ENDDO
363                ENDDO
364                resorted = .TRUE.
365             ELSE
366                to_be_resorted => qv_av
367             ENDIF
368
369          CASE ( 'rho' )
370             IF ( av == 0 )  THEN
371                to_be_resorted => rho
372             ELSE
373                to_be_resorted => rho_av
374             ENDIF
375
376          CASE ( 's' )
377             IF ( av == 0 )  THEN
378                to_be_resorted => q
379             ELSE
380                to_be_resorted => s_av
381             ENDIF
382
383          CASE ( 'sa' )
384             IF ( av == 0 )  THEN
385                to_be_resorted => sa
386             ELSE
387                to_be_resorted => sa_av
388             ENDIF
389
390          CASE ( 'u' )
391             IF ( av == 0 )  THEN
392                to_be_resorted => u
393             ELSE
394                to_be_resorted => u_av
395             ENDIF
396
397          CASE ( 'v' )
398             IF ( av == 0 )  THEN
399                to_be_resorted => v
400             ELSE
401                to_be_resorted => v_av
402             ENDIF
403
404          CASE ( 'vpt' )
405             IF ( av == 0 )  THEN
406                to_be_resorted => vpt
407             ELSE
408                to_be_resorted => vpt_av
409             ENDIF
410
411          CASE ( 'w' )
412             IF ( av == 0 )  THEN
413                to_be_resorted => w
414             ELSE
415                to_be_resorted => w_av
416             ENDIF
417
418          CASE DEFAULT
419!
420!--          User defined quantity
421             CALL user_data_output_mask(av, domask(mid,av,if), found, local_pf )
422             resorted = .TRUE.
423
424             IF ( .NOT. found )  THEN
425                WRITE ( message_string, * ) 'no output available for: ', &
426                                            TRIM( domask(mid,av,if) )
427                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
428             ENDIF
429
430       END SELECT
431
432!
433!--    Resort the array to be output, if not done above
434       IF ( .NOT. resorted )  THEN
435          DO  i = 1, mask_size_l(mid,1)
436             DO  j = 1, mask_size_l(mid,2)
437                DO  k = 1, mask_size_l(mid,3)
438                   local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
439                                      mask_j(mid,j),mask_i(mid,i))
440                ENDDO
441             ENDDO
442          ENDDO
443       ENDIF
444
445!
446!--    I/O block. I/O methods are implemented
447!--    (1) for parallel execution
448!--     a. with netCDF 4 parallel I/O-enabled library
449!--     b. with netCDF 3 library
450!--    (2) for serial execution.
451!--    The choice of method depends on the correct setting of preprocessor
452!--    directives __parallel and __netcdf4_parallel as well as on the parameter
453!--    netcdf_data_format.
454#if defined( __parallel )
455#if defined( __netcdf4_parallel )
456       IF ( netcdf_data_format > 4 )  THEN
457!
458!--       (1) a. Parallel I/O using netCDF 4 (not yet tested)
459          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
460               id_var_domask(mid,av,if),  &
461               local_pf,  &
462               start = (/ mask_start_l(mid,1), mask_start_l(mid,2),  &
463                          mask_start_l(mid,3), domask_time_count(mid,av) /),  &
464               count = (/ mask_size_l(mid,1), mask_size_l(mid,2),  &
465                          mask_size_l(mid,3), 1 /) )
466          CALL handle_netcdf_error( 'data_output_mask', 461 )
467       ELSE
468#endif
469!
470!--       (1) b. Conventional I/O only through PE0
471!--       PE0 receives partial arrays from all processors of the respective mask
472!--       and outputs them. Here a barrier has to be set, because otherwise
473!--       "-MPI- FATAL: Remote protocol queue full" may occur.
474          CALL MPI_BARRIER( comm2d, ierr )
475
476          ngp = mask_size_l(mid,1) * mask_size_l(mid,2) * mask_size_l(mid,3)
477          IF ( myid == 0 )  THEN
478!
479!--          Local array can be relocated directly.
480             total_pf( &
481               mask_start_l(mid,1):mask_start_l(mid,1)+mask_size_l(mid,1)-1, &
482               mask_start_l(mid,2):mask_start_l(mid,2)+mask_size_l(mid,2)-1, &
483               mask_start_l(mid,3):mask_start_l(mid,3)+mask_size_l(mid,3)-1 ) &
484               = local_pf
485!
486!--          Receive data from all other PEs.
487             DO  n = 1, numprocs-1
488!
489!--             Receive index limits first, then array.
490!--             Index limits are received in arbitrary order from the PEs.
491                CALL MPI_RECV( ind(1), 6, MPI_INTEGER, MPI_ANY_SOURCE, 0,  &
492                     comm2d, status, ierr )
493!
494!--             Not all PEs have data for the mask
495                IF ( ind(1) /= -9999 )  THEN
496                   ngp = ( ind(2)-ind(1)+1 ) * (ind(4)-ind(3)+1 ) *  &
497                         ( ind(6)-ind(5)+1 )
498                   sender = status(MPI_SOURCE)
499                   DEALLOCATE( local_pf )
500                   ALLOCATE(local_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)))
501                   CALL MPI_RECV( local_pf(ind(1),ind(3),ind(5)), ngp,  &
502                        MPI_REAL, sender, 1, comm2d, status, ierr )
503                   total_pf(ind(1):ind(2),ind(3):ind(4),ind(5):ind(6)) &
504                        = local_pf
505                ENDIF
506             ENDDO
507
508             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
509                  id_var_domask(mid,av,if), total_pf, &
510                  start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
511                  count = (/ mask_size(mid,1), mask_size(mid,2), &
512                             mask_size(mid,3), 1 /) )
513             CALL handle_netcdf_error( 'data_output_mask', 462 )
514
515          ELSE
516!
517!--          If at least part of the mask resides on the PE, send the index
518!--          limits for the target array, otherwise send -9999 to PE0.
519             IF ( mask_size_l(mid,1) > 0 .AND.  mask_size_l(mid,2) > 0 .AND. &
520                  mask_size_l(mid,3) > 0  ) &
521                  THEN
522                ind(1) = mask_start_l(mid,1)
523                ind(2) = mask_start_l(mid,1) + mask_size_l(mid,1) - 1
524                ind(3) = mask_start_l(mid,2)
525                ind(4) = mask_start_l(mid,2) + mask_size_l(mid,2) - 1
526                ind(5) = mask_start_l(mid,3)
527                ind(6) = mask_start_l(mid,3) + mask_size_l(mid,3) - 1
528             ELSE
529                ind(1) = -9999; ind(2) = -9999
530                ind(3) = -9999; ind(4) = -9999
531                ind(5) = -9999; ind(6) = -9999
532             ENDIF
533             CALL MPI_SEND( ind(1), 6, MPI_INTEGER, 0, 0, comm2d, ierr )
534!
535!--          If applicable, send data to PE0.
536             IF ( ind(1) /= -9999 )  THEN
537                CALL MPI_SEND( local_pf(1,1,1), ngp, MPI_REAL, 0, 1, comm2d, &
538                     ierr )
539             ENDIF
540          ENDIF
541!
542!--       A barrier has to be set, because otherwise some PEs may proceed too
543!--       fast so that PE0 may receive wrong data on tag 0.
544          CALL MPI_BARRIER( comm2d, ierr )
545#if defined( __netcdf4_parallel )
546       ENDIF
547#endif
548#else
549!
550!--    (2) For serial execution of PALM, the single processor (PE0) holds all
551!--    data and writes them directly to file.
552       nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),  &
553            id_var_domask(mid,av,if),       &
554            local_pf, &
555            start = (/ 1, 1, 1, domask_time_count(mid,av) /), &
556            count = (/ mask_size_l(mid,1), mask_size_l(mid,2), &
557                       mask_size_l(mid,3), 1 /) )
558       CALL handle_netcdf_error( 'data_output_mask', 463 )
559#endif
560
561       if = if + 1
562
563    ENDDO
564
565!
566!-- Deallocate temporary arrays.
567    DEALLOCATE( local_pf )
568#if defined( __parallel )
569    IF ( myid == 0 )  THEN
570       DEALLOCATE( total_pf )
571    ENDIF
572#endif
573
574
575    CALL cpu_log( log_point(49), 'data_output_mask', 'stop' )
576#endif
577
578 END SUBROUTINE data_output_mask
Note: See TracBrowser for help on using the repository browser.