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

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

Last commit documented.

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