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

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

last commit documented

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