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

Last change on this file since 673 was 673, checked in by suehring, 13 years ago

Right computation of the pressure using Runge-Kutta weighting coefficients. Consideration of the pressure gradient during the time integration removed. Removed bugfix concerning velocity variances.

  • Property svn:keywords set to Id
File size: 15.6 KB
Line 
1 SUBROUTINE data_output_3d( av )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! When using Multigrid or SOR solver an additional CALL exchange_horiz is
7! is needed for pressure output.
8! Former revisions:
9! -----------------
10! $Id: data_output_3d.f90 673 2011-01-18 16:19:48Z suehring $
11!
12! 667 2010-12-23 12:06:00Z suehring/gryschka
13! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
14! allocation of arrays.  Calls of exchange_horiz are modified.
15! Skip-value skip_do_avs changed to a dynamic adaption of ghost points.
16!
17! 646 2010-12-15 13:03:52Z raasch
18! bugfix: missing define statements for netcdf added
19!
20! 493 2010-03-01 08:30:24Z raasch
21! NetCDF4 support (parallel output)
22!
23! 355 2009-07-17 01:03:01Z letzel
24! simulated_time in NetCDF output replaced by time_since_reference_point.
25! Output of NetCDF messages with aid of message handling routine.
26! Output of messages replaced by message handling routine.
27! Bugfix: to_be_resorted => s_av for time-averaged scalars
28!
29! 96 2007-06-04 08:07:41Z raasch
30! Output of density and salinity
31!
32! 75 2007-03-22 09:54:05Z raasch
33! 2nd+3rd argument removed from exchange horiz
34!
35! RCS Log replace by Id keyword, revision history cleaned up
36!
37! Revision 1.3  2006/06/02 15:18:59  raasch
38! +argument "found", -argument grid in call of routine user_data_output_3d
39!
40! Revision 1.2  2006/02/23 10:23:07  raasch
41! Former subroutine plot_3d renamed data_output_3d, pl.. renamed do..,
42! .._anz renamed .._n,
43! output extended to (almost) all quantities, output of user-defined quantities
44!
45! Revision 1.1  1997/09/03 06:29:36  raasch
46! Initial revision
47!
48!
49! Description:
50! ------------
51! Output of the 3D-arrays in NetCDF and/or AVS format.
52!------------------------------------------------------------------------------!
53
54    USE array_kind
55    USE arrays_3d
56    USE averaging
57    USE cloud_parameters
58    USE control_parameters
59    USE cpulog
60    USE indices
61    USE interfaces
62    USE netcdf_control
63    USE particle_attributes
64    USE pegrid
65
66    IMPLICIT NONE
67
68    CHARACTER (LEN=9) ::  simulated_time_mod
69
70    INTEGER           ::  av, i, if, j, k, n, pos, prec, psi
71
72    LOGICAL           ::  found, resorted
73
74    REAL              ::  mean_r, s_r3, s_r4
75
76    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE  ::  local_pf
77
78    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
79
80!
81!-- Return, if nothing to output
82    IF ( do3d_no(av) == 0 )  RETURN
83
84    CALL cpu_log (log_point(14),'data_output_3d','start')
85
86!
87!-- Open output file.
88!-- Also creates coordinate and fld-file for AVS.
89!-- For classic or 64bit NetCDF output or output of other (old) data formats,
90!-- for a run on more than one PE, each PE opens its own file and
91!-- writes the data of its subdomain in binary format (regardless of the format
92!-- the user has requested). After the run, these files are combined to one
93!-- file by combine_plot_fields in the format requested by the user (netcdf
94!-- and/or avs).
95!-- For NetCDF4/HDF5 output, data is written in parallel into one file.
96    IF ( netcdf_output )  THEN
97       IF ( netcdf_data_format < 3 )  THEN
98          CALL check_open( 30 )
99          IF ( myid == 0 )  CALL check_open( 106+av*10 )
100       ELSE
101          CALL check_open( 106+av*10 )
102       ENDIF
103    ELSE
104       IF ( avs_output  .OR.  ( numprocs > 1 ) )  CALL check_open( 30 )
105    ENDIF
106
107!
108!-- Allocate a temporary array with the desired output dimensions.
109    ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb:nz_do3d) )
110
111!
112!-- Update the NetCDF time axis
113#if defined( __netcdf )
114    IF ( myid == 0  .OR.  netcdf_data_format > 2 )  THEN
115       do3d_time_count(av) = do3d_time_count(av) + 1
116       IF ( netcdf_output )  THEN
117          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av), &
118                                  (/ time_since_reference_point /),  &
119                                  start = (/ do3d_time_count(av) /), &
120                                  count = (/ 1 /) )
121          CALL handle_netcdf_error( 'data_output_3d', 376 )
122       ENDIF
123    ENDIF
124#endif
125
126!
127!-- Loop over all variables to be written.
128    if = 1
129
130    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
131!
132!--    Set the precision for data compression.
133       IF ( do3d_compress )  THEN
134          DO  i = 1, 100
135             IF ( plot_3d_precision(i)%variable == do3d(av,if) )  THEN
136                prec = plot_3d_precision(i)%precision
137                EXIT
138             ENDIF
139          ENDDO
140       ENDIF
141
142!
143!--    Store the array chosen on the temporary array.
144       resorted = .FALSE.
145       SELECT CASE ( TRIM( do3d(av,if) ) )
146
147          CASE ( 'e' )
148             IF ( av == 0 )  THEN
149                to_be_resorted => e
150             ELSE
151                to_be_resorted => e_av
152             ENDIF
153
154          CASE ( 'p' )
155             IF ( psolver == 'multigrid' .OR. psolver == 'sor' )              &
156                CALL exchange_horiz( p, nbgp )
157             IF ( av == 0 )  THEN
158                to_be_resorted => p
159             ELSE
160                to_be_resorted => p_av
161             ENDIF
162
163          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
164             IF ( av == 0 )  THEN
165                tend = prt_count
166                CALL exchange_horiz( tend, nbgp )
167                DO  i = nxlg, nxrg
168                   DO  j = nysg, nyng
169                      DO  k = nzb, nz_do3d
170                         local_pf(i,j,k) = tend(k,j,i)
171                      ENDDO
172                   ENDDO
173                ENDDO
174                resorted = .TRUE.
175             ELSE
176                CALL exchange_horiz( pc_av, nbgp )
177                to_be_resorted => pc_av
178             ENDIF
179
180          CASE ( 'pr' )  ! mean particle radius
181             IF ( av == 0 )  THEN
182                DO  i = nxl, nxr
183                   DO  j = nys, nyn
184                      DO  k = nzb, nzt+1
185                         psi = prt_start_index(k,j,i)
186                         s_r3 = 0.0
187                         s_r4 = 0.0
188                         DO  n = psi, psi+prt_count(k,j,i)-1
189                            s_r3 = s_r3 + particles(n)%radius**3
190                            s_r4 = s_r4 + particles(n)%radius**4
191                         ENDDO
192                         IF ( s_r3 /= 0.0 )  THEN
193                            mean_r = s_r4 / s_r3
194                         ELSE
195                            mean_r = 0.0
196                         ENDIF
197                         tend(k,j,i) = mean_r
198                      ENDDO
199                   ENDDO
200                ENDDO
201                CALL exchange_horiz( tend, nbgp )
202                DO  i = nxlg, nxrg
203                   DO  j = nysg, nyng
204                      DO  k = nzb, nzt+1
205                         local_pf(i,j,k) = tend(k,j,i)
206                      ENDDO
207                   ENDDO
208                ENDDO
209                resorted = .TRUE.
210             ELSE
211                CALL exchange_horiz( pr_av, nbgp )
212                to_be_resorted => pr_av
213             ENDIF
214
215          CASE ( 'pt' )
216             IF ( av == 0 )  THEN
217                IF ( .NOT. cloud_physics ) THEN
218                   to_be_resorted => pt
219                ELSE
220                   DO  i = nxlg, nxrg
221                      DO  j = nysg, nyng
222                         DO  k = nzb, nz_do3d
223                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
224                                                          pt_d_t(k) * &
225                                                          ql(k,j,i)
226                         ENDDO
227                      ENDDO
228                   ENDDO
229                   resorted = .TRUE.
230                ENDIF
231             ELSE
232                to_be_resorted => pt_av
233             ENDIF
234
235          CASE ( 'q' )
236             IF ( av == 0 )  THEN
237                to_be_resorted => q
238             ELSE
239                to_be_resorted => q_av
240             ENDIF
241             
242          CASE ( 'ql' )
243             IF ( av == 0 )  THEN
244                to_be_resorted => ql
245             ELSE
246                to_be_resorted => ql_av
247             ENDIF
248
249          CASE ( 'ql_c' )
250             IF ( av == 0 )  THEN
251                to_be_resorted => ql_c
252             ELSE
253                to_be_resorted => ql_c_av
254             ENDIF
255
256          CASE ( 'ql_v' )
257             IF ( av == 0 )  THEN
258                to_be_resorted => ql_v
259             ELSE
260                to_be_resorted => ql_v_av
261             ENDIF
262
263          CASE ( 'ql_vp' )
264             IF ( av == 0 )  THEN
265                to_be_resorted => ql_vp
266             ELSE
267                to_be_resorted => ql_vp_av
268             ENDIF
269
270          CASE ( 'qv' )
271             IF ( av == 0 )  THEN
272                DO  i = nxlg, nxrg
273                   DO  j = nysg, nyng
274                      DO  k = nzb, nz_do3d
275                         local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
276                      ENDDO
277                   ENDDO
278                ENDDO
279                resorted = .TRUE.
280             ELSE
281                to_be_resorted => qv_av
282             ENDIF
283
284          CASE ( 'rho' )
285             IF ( av == 0 )  THEN
286                to_be_resorted => rho
287             ELSE
288                to_be_resorted => rho_av
289             ENDIF
290             
291          CASE ( 's' )
292             IF ( av == 0 )  THEN
293                to_be_resorted => q
294             ELSE
295                to_be_resorted => s_av
296             ENDIF
297             
298          CASE ( 'sa' )
299             IF ( av == 0 )  THEN
300                to_be_resorted => sa
301             ELSE
302                to_be_resorted => sa_av
303             ENDIF
304             
305          CASE ( 'u' )
306             IF ( av == 0 )  THEN
307                to_be_resorted => u
308             ELSE
309                to_be_resorted => u_av
310             ENDIF
311
312          CASE ( 'v' )
313             IF ( av == 0 )  THEN
314                to_be_resorted => v
315             ELSE
316                to_be_resorted => v_av
317             ENDIF
318
319          CASE ( 'vpt' )
320             IF ( av == 0 )  THEN
321                to_be_resorted => vpt
322             ELSE
323                to_be_resorted => vpt_av
324             ENDIF
325
326          CASE ( 'w' )
327             IF ( av == 0 )  THEN
328                to_be_resorted => w
329             ELSE
330                to_be_resorted => w_av
331             ENDIF
332
333          CASE DEFAULT
334!
335!--          User defined quantity
336             CALL user_data_output_3d( av, do3d(av,if), found, local_pf, &
337                                       nz_do3d )
338             resorted = .TRUE.
339
340             IF ( .NOT. found )  THEN
341                message_string =  'no output available for: ' //   &
342                                  TRIM( do3d(av,if) )
343                CALL message( 'data_output_3d', 'PA0182', 0, 0, 0, 6, 0 )
344             ENDIF
345
346       END SELECT
347
348!
349!--    Resort the array to be output, if not done above
350       IF ( .NOT. resorted )  THEN
351          DO  i = nxlg, nxrg
352             DO  j = nysg, nyng
353                DO  k = nzb, nz_do3d
354                   local_pf(i,j,k) = to_be_resorted(k,j,i)
355                ENDDO
356             ENDDO
357          ENDDO
358       ENDIF
359
360!
361!--    Output of the volume data information for the AVS-FLD-file.
362       do3d_avs_n = do3d_avs_n + 1
363       IF ( myid == 0  .AND.  avs_output )  THEN
364!
365!--       AVS-labels must not contain any colons. Hence they must be removed
366!--       from the time character string.
367          simulated_time_mod = simulated_time_chr
368          DO  WHILE ( SCAN( simulated_time_mod, ':' ) /= 0 )
369             pos = SCAN( simulated_time_mod, ':' )
370             simulated_time_mod(pos:pos) = '/'
371          ENDDO
372
373          IF ( av == 0 )  THEN
374             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
375                                 skip_do_avs, TRIM( do3d(av,if) ), &
376                                 TRIM( simulated_time_mod )
377          ELSE
378             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
379                                 skip_do_avs, TRIM( do3d(av,if) ) // &
380                                 ' averaged', TRIM( simulated_time_mod )
381          ENDIF
382!
383!--       Determine the Skip-value for the next array. Record end and start
384!--       require 4 byte each.
385          skip_do_avs = skip_do_avs + ( ((nx+2*nbgp)*(ny+2*nbgp)*(nz_do3d+1)) * 4 + 8 )
386       ENDIF
387
388!
389!--    Output of the 3D-array. (compressed/uncompressed)
390       IF ( do3d_compress )  THEN
391!
392!--       Compression, output of compression information on FLD-file and output
393!--       of compressed data.
394          CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, &
395                                 nzb, nz_do3d, prec, nbgp )
396       ELSE
397!
398!--       Uncompressed output.
399#if defined( __parallel )
400          IF ( netcdf_output )  THEN
401             IF ( netcdf_data_format < 3 )  THEN
402!
403!--             Classic or 64bit format. Data is output in parallel in FORTRAN
404!--             binary format here, and later collected into one file by
405!--             combine_plot_fields
406                IF ( myid == 0 )  THEN
407                   WRITE ( 30 )  simulated_time, do3d_time_count(av), av
408                ENDIF
409                WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb, nz_do3d
410                WRITE ( 30 )  local_pf
411
412             ELSE
413#if defined( __netcdf )
414!
415!--             Output in NetCDF4/HDF5 format.
416!--             Do not output redundant ghost point data except for the
417!--             boundaries of the total domain.
418                IF ( nxr == nx  .AND.  nyn /= ny )  THEN
419                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
420                                  local_pf(nxl:nxrg,nys:nyn,nzb:nz_do3d),    &
421                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
422                      count = (/ nxr-nxl+1+nbgp, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
423                ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
424                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
425                                  local_pf(nxl:nxr,nys:nyng,nzb:nz_do3d),    &
426                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
427                      count = (/ nxr-nxl+1, nyn-nys+1+nbgp, nz_do3d-nzb+1, 1 /) )
428                ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
429                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
430                                  local_pf(nxl:nxrg,nys:nyng,nzb:nz_do3d),  &
431                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
432                      count = (/ nxr-nxl+1+nbgp, nyn-nys+1+nbgp, nz_do3d-nzb+1, 1 /) )
433                ELSE
434                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
435                                  local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d),      &
436                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
437                      count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
438                ENDIF
439                CALL handle_netcdf_error( 'data_output_3d', 386 )
440#endif
441             ENDIF
442          ENDIF
443#else
444          IF ( avs_output )  THEN
445             WRITE ( 30 )  local_pf(nxl:nxr+1,nys:nyn+1,:)
446          ENDIF
447#if defined( __netcdf )
448          IF ( netcdf_output )  THEN
449
450             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),    &
451                               local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
452                               start = (/ 1, 1, 1, do3d_time_count(av) /), &
453                               count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
454             CALL handle_netcdf_error( 'data_output_3d', 446 )
455
456          ENDIF
457#endif
458#endif
459       ENDIF
460
461       if = if + 1
462
463    ENDDO
464
465!
466!-- Deallocate temporary array.
467    DEALLOCATE( local_pf )
468
469
470    CALL cpu_log (log_point(14),'data_output_3d','stop','nobarrier')
471
472!
473!-- Formats.
4743300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/ &
475             'label = ',A,A)
476
477 END SUBROUTINE data_output_3d
Note: See TracBrowser for help on using the repository browser.