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

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

Bugfix in exchange of ghost layers for p.

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