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

Last change on this file since 771 was 771, checked in by heinze, 12 years ago

Output of liquid water potential temperature in case of cloud_physics=.T. enabled

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