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

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

last commit documented

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