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

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

Bugfix in output of p_av.

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