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

Last change on this file since 1353 was 1353, checked in by heinze, 10 years ago

REAL constants provided with KIND-attribute

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