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

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

Last commit documented.

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