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

Last change on this file since 254 was 254, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

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