source: palm/trunk/SOURCE/data_output_3d.f90 @ 1319

Last change on this file since 1319 was 1319, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 21.3 KB
Line 
1 SUBROUTINE data_output_3d( 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_3d.f90 1319 2014-03-17 15:08:44Z raasch $
27!
28! 1318 2014-03-17 13:35:16Z raasch
29! barrier argument removed from cpu_log,
30! module interfaces removed
31!
32! 1308 2014-03-13 14:58:42Z fricke
33! Check, if the limit of the time dimension is exceeded for parallel output
34! To increase the performance for parallel output, the following is done:
35! - Update of time axis is only done by PE0
36!
37! 1244 2013-10-31 08:16:56Z raasch
38! Bugfix for index bounds in case of 3d-parallel output
39!
40! 1115 2013-03-26 18:16:16Z hoffmann
41! ql is calculated by calc_liquid_water_content
42!
43! 1106 2013-03-04 05:31:38Z raasch
44! array_kind renamed precision_kind
45!
46! 1076 2012-12-05 08:30:18Z hoffmann
47! Bugfix in output of ql
48!
49! 1053 2012-11-13 17:11:03Z hoffmann
50! +nr, qr, prr, qc and averaged quantities
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: missing calculation of ql_vp added
60!
61! 790 2011-11-29 03:11:20Z raasch
62! bugfix: calculation of 'pr' must depend on the particle weighting factor,
63! nzt+1 replaced by nz_do3d for 'pr'
64!
65! 771 2011-10-27 10:56:21Z heinze
66! +lpt
67!
68! 759 2011-09-15 13:58:31Z raasch
69! Splitting of parallel I/O
70!
71! 727 2011-04-20 20:05:25Z suehring
72! Exchange ghost layers also for p_av.
73!
74! 725 2011-04-11 09:37:01Z suehring
75! Exchange ghost layers for p regardless of used pressure solver (except SOR).
76!
77! 691 2011-03-04 08:45:30Z maronga
78! Replaced simulated_time by time_since_reference_point
79!
80! 673 2011-01-18 16:19:48Z suehring
81! When using Multigrid or SOR solver an additional CALL exchange_horiz is
82! is needed for pressure output.
83!
84! 667 2010-12-23 12:06:00Z suehring/gryschka
85! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
86! allocation of arrays.  Calls of exchange_horiz are modified.
87! Skip-value skip_do_avs changed to a dynamic adaption of ghost points.
88!
89! 646 2010-12-15 13:03:52Z raasch
90! bugfix: missing define statements for netcdf added
91!
92! 493 2010-03-01 08:30:24Z raasch
93! netCDF4 support (parallel output)
94!
95! 355 2009-07-17 01:03:01Z letzel
96! simulated_time in netCDF output replaced by time_since_reference_point.
97! Output of netCDF messages with aid of message handling routine.
98! Output of messages replaced by message handling routine.
99! Bugfix: to_be_resorted => s_av for time-averaged scalars
100!
101! 96 2007-06-04 08:07:41Z raasch
102! Output of density and salinity
103!
104! 75 2007-03-22 09:54:05Z raasch
105! 2nd+3rd argument removed from exchange horiz
106!
107! RCS Log replace by Id keyword, revision history cleaned up
108!
109! Revision 1.3  2006/06/02 15:18:59  raasch
110! +argument "found", -argument grid in call of routine user_data_output_3d
111!
112! Revision 1.2  2006/02/23 10:23:07  raasch
113! Former subroutine plot_3d renamed data_output_3d, pl.. renamed do..,
114! .._anz renamed .._n,
115! output extended to (almost) all quantities, output of user-defined quantities
116!
117! Revision 1.1  1997/09/03 06:29:36  raasch
118! Initial revision
119!
120!
121! Description:
122! ------------
123! Output of the 3D-arrays in netCDF and/or AVS format.
124!------------------------------------------------------------------------------!
125
126    USE arrays_3d
127    USE averaging
128    USE cloud_parameters
129    USE control_parameters
130    USE cpulog
131    USE indices
132    USE netcdf_control
133    USE particle_attributes
134    USE pegrid
135    USE precision_kind
136
137    IMPLICIT NONE
138
139    CHARACTER (LEN=9) ::  simulated_time_mod
140
141    INTEGER           ::  av, i, if, j, k, n, pos, prec, psi
142
143    LOGICAL           ::  found, resorted
144
145    REAL              ::  mean_r, s_r3, s_r4
146
147    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE  ::  local_pf
148
149    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
150
151!
152!-- Return, if nothing to output
153    IF ( do3d_no(av) == 0 )  RETURN
154!
155!-- For parallel netcdf output the time axis must be limited. Return, if this
156!-- limit is exceeded. This could be the case, if the simulated time exceeds
157!-- the given end time by the length of the given output interval.
158    IF ( netcdf_data_format > 4 )  THEN
159       IF ( do3d_time_count(av) + 1 > ntdim_3d(av) )  THEN
160          WRITE ( message_string, * ) 'Output of 3d data is not given at t=',  &
161                                      simulated_time, '&because the maximum ', & 
162                                      'number of output time levels is ',      &
163                                      'exceeded.'
164          CALL message( 'data_output_3d', 'PA0387', 0, 1, 0, 6, 0 )         
165          RETURN
166       ENDIF
167    ENDIF
168
169    CALL cpu_log (log_point(14),'data_output_3d','start')
170
171!
172!-- Open output file.
173!-- Also creates coordinate and fld-file for AVS.
174!-- For classic or 64bit netCDF output or output of other (old) data formats,
175!-- for a run on more than one PE, each PE opens its own file and
176!-- writes the data of its subdomain in binary format (regardless of the format
177!-- the user has requested). After the run, these files are combined to one
178!-- file by combine_plot_fields in the format requested by the user (netcdf
179!-- and/or avs).
180!-- For netCDF4/HDF5 output, data is written in parallel into one file.
181    IF ( netcdf_output )  THEN
182       IF ( netcdf_data_format < 5 )  THEN
183          CALL check_open( 30 )
184          IF ( myid == 0 )  CALL check_open( 106+av*10 )
185       ELSE
186          CALL check_open( 106+av*10 )
187       ENDIF
188    ELSE
189       IF ( avs_output  .OR.  ( numprocs > 1 ) )  CALL check_open( 30 )
190    ENDIF
191
192!
193!-- Allocate a temporary array with the desired output dimensions.
194    ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb:nz_do3d) )
195
196!
197!-- Update the netCDF time axis
198!-- In case of parallel output, this is only done by PE0 to increase the
199!-- performance.
200#if defined( __netcdf )
201    do3d_time_count(av) = do3d_time_count(av) + 1
202    IF ( myid == 0 )  THEN
203       IF ( netcdf_output )  THEN
204          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av), &
205                                  (/ time_since_reference_point /),  &
206                                  start = (/ do3d_time_count(av) /), &
207                                  count = (/ 1 /) )
208          CALL handle_netcdf_error( 'data_output_3d', 376 )
209       ENDIF
210    ENDIF
211#endif
212
213!
214!-- Loop over all variables to be written.
215    if = 1
216
217    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
218!
219!--    Set the precision for data compression.
220       IF ( do3d_compress )  THEN
221          DO  i = 1, 100
222             IF ( plot_3d_precision(i)%variable == do3d(av,if) )  THEN
223                prec = plot_3d_precision(i)%precision
224                EXIT
225             ENDIF
226          ENDDO
227       ENDIF
228
229!
230!--    Store the array chosen on the temporary array.
231       resorted = .FALSE.
232       SELECT CASE ( TRIM( do3d(av,if) ) )
233
234          CASE ( 'e' )
235             IF ( av == 0 )  THEN
236                to_be_resorted => e
237             ELSE
238                to_be_resorted => e_av
239             ENDIF
240
241          CASE ( 'lpt' )
242             IF ( av == 0 )  THEN
243                to_be_resorted => pt
244             ELSE
245                to_be_resorted => lpt_av
246             ENDIF
247
248          CASE ( 'nr' )
249             IF ( av == 0 )  THEN
250                to_be_resorted => nr
251             ELSE
252                to_be_resorted => nr_av
253             ENDIF
254
255          CASE ( 'p' )
256             IF ( av == 0 )  THEN
257                IF ( psolver /= 'sor' )  CALL exchange_horiz( p, nbgp )
258                to_be_resorted => p
259             ELSE
260                IF ( psolver /= 'sor' )  CALL exchange_horiz( p_av, nbgp )
261                to_be_resorted => p_av
262             ENDIF
263
264          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
265             IF ( av == 0 )  THEN
266                tend = prt_count
267                CALL exchange_horiz( tend, nbgp )
268                DO  i = nxlg, nxrg
269                   DO  j = nysg, nyng
270                      DO  k = nzb, nz_do3d
271                         local_pf(i,j,k) = tend(k,j,i)
272                      ENDDO
273                   ENDDO
274                ENDDO
275                resorted = .TRUE.
276             ELSE
277                CALL exchange_horiz( pc_av, nbgp )
278                to_be_resorted => pc_av
279             ENDIF
280
281          CASE ( 'pr' )  ! mean particle radius
282             IF ( av == 0 )  THEN
283                DO  i = nxl, nxr
284                   DO  j = nys, nyn
285                      DO  k = nzb, nz_do3d
286                         psi = prt_start_index(k,j,i)
287                         s_r3 = 0.0
288                         s_r4 = 0.0
289                         DO  n = psi, psi+prt_count(k,j,i)-1
290                         s_r3 = s_r3 + particles(n)%radius**3 * &
291                                       particles(n)%weight_factor
292                         s_r4 = s_r4 + particles(n)%radius**4 * &
293                                       particles(n)%weight_factor
294                         ENDDO
295                         IF ( s_r3 /= 0.0 )  THEN
296                            mean_r = s_r4 / s_r3
297                         ELSE
298                            mean_r = 0.0
299                         ENDIF
300                         tend(k,j,i) = mean_r
301                      ENDDO
302                   ENDDO
303                ENDDO
304                CALL exchange_horiz( tend, nbgp )
305                DO  i = nxlg, nxrg
306                   DO  j = nysg, nyng
307                      DO  k = nzb, nz_do3d
308                         local_pf(i,j,k) = tend(k,j,i)
309                      ENDDO
310                   ENDDO
311                ENDDO
312                resorted = .TRUE.
313             ELSE
314                CALL exchange_horiz( pr_av, nbgp )
315                to_be_resorted => pr_av
316             ENDIF
317
318          CASE ( 'prr' )
319             IF ( av == 0 )  THEN
320                CALL exchange_horiz( prr, nbgp )
321                DO  i = nxlg, nxrg
322                   DO  j = nysg, nyng
323                      DO  k = nzb, nzt+1
324                         local_pf(i,j,k) = prr(k,j,i)
325                      ENDDO
326                   ENDDO
327                ENDDO
328             ELSE
329                CALL exchange_horiz( prr_av, nbgp )
330                DO  i = nxlg, nxrg
331                   DO  j = nysg, nyng
332                      DO  k = nzb, nzt+1
333                         local_pf(i,j,k) = prr_av(k,j,i)
334                      ENDDO
335                   ENDDO
336                ENDDO
337             ENDIF
338             resorted = .TRUE.
339
340          CASE ( 'pt' )
341             IF ( av == 0 )  THEN
342                IF ( .NOT. cloud_physics ) THEN
343                   to_be_resorted => pt
344                ELSE
345                   DO  i = nxlg, nxrg
346                      DO  j = nysg, nyng
347                         DO  k = nzb, nz_do3d
348                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
349                                                          pt_d_t(k) * &
350                                                          ql(k,j,i)
351                         ENDDO
352                      ENDDO
353                   ENDDO
354                   resorted = .TRUE.
355                ENDIF
356             ELSE
357                to_be_resorted => pt_av
358             ENDIF
359
360          CASE ( 'q' )
361             IF ( av == 0 )  THEN
362                to_be_resorted => q
363             ELSE
364                to_be_resorted => q_av
365             ENDIF
366
367          CASE ( 'qc' )
368             IF ( av == 0 )  THEN
369                to_be_resorted => qc
370             ELSE
371                to_be_resorted => qc_av
372             ENDIF
373
374          CASE ( 'ql' )
375             IF ( av == 0 )  THEN
376                to_be_resorted => ql
377             ELSE
378                to_be_resorted => ql_av
379             ENDIF
380
381          CASE ( 'ql_c' )
382             IF ( av == 0 )  THEN
383                to_be_resorted => ql_c
384             ELSE
385                to_be_resorted => ql_c_av
386             ENDIF
387
388          CASE ( 'ql_v' )
389             IF ( av == 0 )  THEN
390                to_be_resorted => ql_v
391             ELSE
392                to_be_resorted => ql_v_av
393             ENDIF
394
395          CASE ( 'ql_vp' )
396             IF ( av == 0 )  THEN
397                DO  i = nxl, nxr
398                   DO  j = nys, nyn
399                      DO  k = nzb, nz_do3d
400                         psi = prt_start_index(k,j,i)
401                         DO  n = psi, psi+prt_count(k,j,i)-1
402                            tend(k,j,i) = tend(k,j,i) + &
403                                          particles(n)%weight_factor / &
404                                          prt_count(k,j,i)
405                         ENDDO
406                      ENDDO
407                   ENDDO
408                ENDDO
409                CALL exchange_horiz( tend, nbgp )
410                DO  i = nxlg, nxrg
411                   DO  j = nysg, nyng
412                      DO  k = nzb, nz_do3d
413                         local_pf(i,j,k) = tend(k,j,i)
414                      ENDDO
415                   ENDDO
416                ENDDO
417                resorted = .TRUE.
418             ELSE
419                CALL exchange_horiz( ql_vp_av, nbgp )
420                to_be_resorted => ql_vp_av
421             ENDIF
422
423          CASE ( 'qr' )
424             IF ( av == 0 )  THEN
425                to_be_resorted => qr
426             ELSE
427                to_be_resorted => qr_av
428             ENDIF
429
430          CASE ( 'qv' )
431             IF ( av == 0 )  THEN
432                DO  i = nxlg, nxrg
433                   DO  j = nysg, nyng
434                      DO  k = nzb, nz_do3d
435                         local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
436                      ENDDO
437                   ENDDO
438                ENDDO
439                resorted = .TRUE.
440             ELSE
441                to_be_resorted => qv_av
442             ENDIF
443
444          CASE ( 'rho' )
445             IF ( av == 0 )  THEN
446                to_be_resorted => rho
447             ELSE
448                to_be_resorted => rho_av
449             ENDIF
450
451          CASE ( 's' )
452             IF ( av == 0 )  THEN
453                to_be_resorted => q
454             ELSE
455                to_be_resorted => s_av
456             ENDIF
457
458          CASE ( 'sa' )
459             IF ( av == 0 )  THEN
460                to_be_resorted => sa
461             ELSE
462                to_be_resorted => sa_av
463             ENDIF
464
465          CASE ( 'u' )
466             IF ( av == 0 )  THEN
467                to_be_resorted => u
468             ELSE
469                to_be_resorted => u_av
470             ENDIF
471
472          CASE ( 'v' )
473             IF ( av == 0 )  THEN
474                to_be_resorted => v
475             ELSE
476                to_be_resorted => v_av
477             ENDIF
478
479          CASE ( 'vpt' )
480             IF ( av == 0 )  THEN
481                to_be_resorted => vpt
482             ELSE
483                to_be_resorted => vpt_av
484             ENDIF
485
486          CASE ( 'w' )
487             IF ( av == 0 )  THEN
488                to_be_resorted => w
489             ELSE
490                to_be_resorted => w_av
491             ENDIF
492
493          CASE DEFAULT
494!
495!--          User defined quantity
496             CALL user_data_output_3d( av, do3d(av,if), found, local_pf, &
497                                       nz_do3d )
498             resorted = .TRUE.
499
500             IF ( .NOT. found )  THEN
501                message_string =  'no output available for: ' //   &
502                                  TRIM( do3d(av,if) )
503                CALL message( 'data_output_3d', 'PA0182', 0, 0, 0, 6, 0 )
504             ENDIF
505
506       END SELECT
507
508!
509!--    Resort the array to be output, if not done above
510       IF ( .NOT. resorted )  THEN
511          DO  i = nxlg, nxrg
512             DO  j = nysg, nyng
513                DO  k = nzb, nz_do3d
514                   local_pf(i,j,k) = to_be_resorted(k,j,i)
515                ENDDO
516             ENDDO
517          ENDDO
518       ENDIF
519
520!
521!--    Output of the volume data information for the AVS-FLD-file.
522       do3d_avs_n = do3d_avs_n + 1
523       IF ( myid == 0  .AND.  avs_output )  THEN
524!
525!--       AVS-labels must not contain any colons. Hence they must be removed
526!--       from the time character string.
527          simulated_time_mod = simulated_time_chr
528          DO  WHILE ( SCAN( simulated_time_mod, ':' ) /= 0 )
529             pos = SCAN( simulated_time_mod, ':' )
530             simulated_time_mod(pos:pos) = '/'
531          ENDDO
532
533          IF ( av == 0 )  THEN
534             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
535                                 skip_do_avs, TRIM( do3d(av,if) ), &
536                                 TRIM( simulated_time_mod )
537          ELSE
538             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
539                                 skip_do_avs, TRIM( do3d(av,if) ) // &
540                                 ' averaged', TRIM( simulated_time_mod )
541          ENDIF
542!
543!--       Determine the Skip-value for the next array. Record end and start
544!--       require 4 byte each.
545          skip_do_avs = skip_do_avs + ( ( ( nx+2*nbgp ) * ( ny+2*nbgp ) * &
546                                          ( nz_do3d+1 ) ) * 4 + 8 )
547       ENDIF
548
549!
550!--    Output of the 3D-array. (compressed/uncompressed)
551       IF ( do3d_compress )  THEN
552!
553!--       Compression, output of compression information on FLD-file and output
554!--       of compressed data.
555          CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, &
556                                 nzb, nz_do3d, prec, nbgp )
557       ELSE
558!
559!--       Uncompressed output.
560#if defined( __parallel )
561          IF ( netcdf_output )  THEN
562             IF ( netcdf_data_format < 5 )  THEN
563!
564!--             Non-parallel netCDF output. Data is output in parallel in
565!--             FORTRAN binary format here, and later collected into one file by
566!--             combine_plot_fields
567                IF ( myid == 0 )  THEN
568                   WRITE ( 30 )  time_since_reference_point,                   &
569                                 do3d_time_count(av), av
570                ENDIF
571                DO  i = 0, io_blocks-1
572                   IF ( i == io_group )  THEN
573                      WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb, nz_do3d
574                      WRITE ( 30 )  local_pf
575                   ENDIF
576#if defined( __parallel )
577                   CALL MPI_BARRIER( comm2d, ierr )
578#endif
579                ENDDO
580
581             ELSE
582#if defined( __netcdf )
583!
584!--             Parallel output in netCDF4/HDF5 format.
585!--             Do not output redundant ghost point data except for the
586!--             boundaries of the total domain.
587                IF ( nxr == nx  .AND.  nyn /= ny )  THEN
588                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
589                                     local_pf(nxl:nxr+1,nys:nyn,nzb:nz_do3d), &
590                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
591                      count = (/ nxr-nxl+2, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
592                ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
593                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
594                                     local_pf(nxl:nxr,nys:nyn+1,nzb:nz_do3d), &
595                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
596                      count = (/ nxr-nxl+1, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
597                ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
598                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
599                                   local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d), &
600                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
601                      count = (/ nxr-nxl+2, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
602                ELSE
603                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
604                                       local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d), &
605                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
606                      count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
607                ENDIF
608                CALL handle_netcdf_error( 'data_output_3d', 386 )
609#endif
610             ENDIF
611          ENDIF
612#else
613          IF ( avs_output )  THEN
614             WRITE ( 30 )  local_pf(nxl:nxr+1,nys:nyn+1,:)
615          ENDIF
616#if defined( __netcdf )
617          IF ( netcdf_output )  THEN
618
619             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),    &
620                               local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
621                               start = (/ 1, 1, 1, do3d_time_count(av) /), &
622                               count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
623             CALL handle_netcdf_error( 'data_output_3d', 446 )
624
625          ENDIF
626#endif
627#endif
628       ENDIF
629
630       if = if + 1
631
632    ENDDO
633
634!
635!-- Deallocate temporary array.
636    DEALLOCATE( local_pf )
637
638
639    CALL cpu_log( log_point(14), 'data_output_3d', 'stop' )
640
641!
642!-- Formats.
6433300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/ &
644             'label = ',A,A)
645
646 END SUBROUTINE data_output_3d
Note: See TracBrowser for help on using the repository browser.