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

Last change on this file since 719 was 692, checked in by maronga, 13 years ago

last commit documented

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