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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 12.8 KB
Line 
1 SUBROUTINE data_output_3d( av )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: data_output_3d.f90,v $
11! Revision 1.3  2006/06/02 15:18:59  raasch
12! +argument "found", -argument grid in call of routine user_data_output_3d
13!
14! Revision 1.2  2006/02/23 10:23:07  raasch
15! Former subroutine plot_3d renamed data_output_3d, pl.. renamed do..,
16! .._anz renamed .._n,
17! output extended to (almost) all quantities, output of user-defined quantities
18!
19! Revision 1.1  2006/02/23 10:21:34  raasch
20! Initial revision
21!
22! Revision 1.13  2005/06/26 20:08:36  raasch
23! +ql_c, ql_v, ql_vp
24!
25! Revision 1.12  2005/05/18 15:47:34  raasch
26! Extensions for NetCDF output
27!
28! Revision 1.11  2003/03/16 09:42:31  raasch
29! Two underscores (_) are placed in front of all define-strings
30!
31! Revision 1.10  2002/06/11 13:13:27  raasch
32! TRIM function added (needed on IBM-systems)
33!
34! Revision 1.9  2002/04/16  08:11:50  08:11:50  raasch (Siegfried Raasch)
35! Output of scalar field s allowed
36!
37! Revision 1.8  2001/03/30 07:44:45  raasch
38! Translation of remaining German identifiers (variables, subroutines, etc.)
39!
40! Revision 1.7  2001/03/09 21:46:23  letzel
41! All comments translated into English.
42!
43! Revision 1.6  2001/01/22 07:40:10  raasch
44! Module test_variables removed
45!
46! Revision 1.5  2000/04/13 14:02:39  schroeter
47! Plotausgabe fuer Gesamtwasser- und Fluessigwassergehalt sowie potentielle
48! Fluessigwassertemperatur
49!
50! Revision 1.4  99/03/02  09:24:51  09:24:51  raasch (Siegfried Raasch)
51! Datenkompression implementiert
52!
53! Revision 1.3  1998/07/06 12:26:35  raasch
54! + USE test_variables
55!
56! Revision 1.2  1998/03/09 16:24:33  raasch
57! simulated_time_mod verlaengert
58!
59! Revision 1.1  1997/09/03 06:29:36  raasch
60! Initial revision
61!
62!
63! Description:
64! ------------
65! Output of the 3D-arrays in NetCDF and/or AVS format.
66!------------------------------------------------------------------------------!
67
68    USE array_kind
69    USE arrays_3d
70    USE averaging
71    USE cloud_parameters
72    USE control_parameters
73    USE cpulog
74    USE indices
75    USE interfaces
76    USE netcdf_control
77    USE particle_attributes
78    USE pegrid
79
80    IMPLICIT NONE
81
82    CHARACTER (LEN=9) ::  simulated_time_mod
83
84    INTEGER           ::  av, i, if, j, k, n, pos, prec, psi
85
86    LOGICAL           ::  found, resorted
87
88    REAL              ::  mean_r, s_r3, s_r4
89
90    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE  ::  local_pf
91
92    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
93
94!
95!-- Return, if nothing to output
96    IF ( do3d_no(av) == 0 )  RETURN
97
98    CALL cpu_log (log_point(14),'data_output_3d','start')
99
100!
101!-- Open output file.
102!-- Also creates coordinate and fld-file for AVS.
103!-- In case of a run on more than one PE, each PE opens its own file and
104!-- writes the data of its subdomain in binary format (regardless of the format
105!-- the user has requested). After the run, these files are combined to one
106!-- file by combine_plot_fields in the format requested by the user (netcdf
107!-- and/or avs).
108    IF ( avs_output  .OR.  ( numprocs > 1 ) )  CALL check_open( 30 )
109
110#if defined( __netcdf )
111    IF ( myid == 0  .AND.  netcdf_output )  CALL check_open( 106+av*10 )
112#endif
113
114!
115!-- Allocate a temporary array with the desired output dimensions.
116    ALLOCATE( local_pf(nxl-1:nxr+1,nys-1:nyn+1,nzb:nz_do3d) )
117
118!
119!-- Update the NetCDF time axis
120#if defined( __netcdf )
121    do3d_time_count(av) = do3d_time_count(av) + 1
122    IF ( myid == 0  .AND.  netcdf_output )  THEN
123       nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av), &
124                               (/ simulated_time /),              &
125                               start = (/ do3d_time_count(av) /), &
126                               count = (/ 1 /) )
127       IF (nc_stat /= NF90_NOERR)  CALL handle_netcdf_error( 1009 )
128    ENDIF
129#endif
130
131!
132!-- Loop over all variables to be written.
133    if = 1
134
135    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
136!
137!--    Set the precision for data compression.
138       IF ( do3d_compress )  THEN
139          DO  i = 1, 100
140             IF ( plot_3d_precision(i)%variable == do3d(av,if) )  THEN
141                prec = plot_3d_precision(i)%precision
142                EXIT
143             ENDIF
144          ENDDO
145       ENDIF
146
147!
148!--    Store the array chosen on the temporary array.
149       resorted = .FALSE.
150       SELECT CASE ( TRIM( do3d(av,if) ) )
151
152          CASE ( 'e' )
153             IF ( av == 0 )  THEN
154                to_be_resorted => e
155             ELSE
156                to_be_resorted => e_av
157             ENDIF
158
159          CASE ( 'p' )
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, 0, 0 )
170                DO  i = nxl-1, nxr+1
171                   DO  j = nys-1, nyn+1
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, 0, 0 )
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, 0, 0 )
205                DO  i = nxl-1, nxr+1
206                   DO  j = nys-1, nyn+1
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, 0, 0 )
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 = nxl-1, nxr+1
224                      DO  j = nys-1, nyn+1
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 = nxl-1, nxr+1
276                   DO  j = nys-1, nyn+1
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 ( 's' )
288             IF ( av == 0 )  THEN
289                to_be_resorted => q
290             ELSE
291                to_be_resorted => q_av
292             ENDIF
293             
294          CASE ( 'u' )
295             IF ( av == 0 )  THEN
296                to_be_resorted => u
297             ELSE
298                to_be_resorted => u_av
299             ENDIF
300
301          CASE ( 'v' )
302             IF ( av == 0 )  THEN
303                to_be_resorted => v
304             ELSE
305                to_be_resorted => v_av
306             ENDIF
307
308          CASE ( 'vpt' )
309             IF ( av == 0 )  THEN
310                to_be_resorted => vpt
311             ELSE
312                to_be_resorted => vpt_av
313             ENDIF
314
315          CASE ( 'w' )
316             IF ( av == 0 )  THEN
317                to_be_resorted => w
318             ELSE
319                to_be_resorted => w_av
320             ENDIF
321
322          CASE DEFAULT
323!
324!--          User defined quantity
325             CALL user_data_output_3d( av, do3d(av,if), found, local_pf, &
326                                       nz_do3d )
327             resorted = .TRUE.
328
329             IF ( myid == 0  .AND.  .NOT. found )  THEN
330                PRINT*, '+++ data_output_3d: no output available for: ', &
331                             do3d(av,if)
332             ENDIF
333
334       END SELECT
335
336!
337!--    Resort the array to be output, if not done above
338       IF ( .NOT. resorted )  THEN
339          DO  i = nxl-1, nxr+1
340             DO  j = nys-1, nyn+1
341                DO  k = nzb, nz_do3d
342                   local_pf(i,j,k) = to_be_resorted(k,j,i)
343                ENDDO
344             ENDDO
345          ENDDO
346       ENDIF
347
348!
349!--    Output of the volume data information for the AVS-FLD-file.
350       do3d_avs_n = do3d_avs_n + 1
351       IF ( myid == 0  .AND.  avs_output )  THEN
352!
353!--       AVS-labels must not contain any colons. Hence they must be removed
354!--       from the time character string.
355          simulated_time_mod = simulated_time_chr
356          DO  WHILE ( SCAN( simulated_time_mod, ':' ) /= 0 )
357             pos = SCAN( simulated_time_mod, ':' )
358             simulated_time_mod(pos:pos) = '/'
359          ENDDO
360
361          IF ( av == 0 )  THEN
362             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
363                                 skip_do_avs, TRIM( do3d(av,if) ), &
364                                 TRIM( simulated_time_mod )
365          ELSE
366             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
367                                 skip_do_avs, TRIM( do3d(av,if) ) // &
368                                 ' averaged', TRIM( simulated_time_mod )
369          ENDIF
370!
371!--       Determine the Skip-value for the next array. Record end and start
372!--       require 4 byte each.
373          skip_do_avs = skip_do_avs + ( ((nx+2)*(ny+2)*(nz_do3d+1)) * 4 + 8 )
374       ENDIF
375
376!
377!--    Output of the 3D-array. (compressed/uncompressed)
378       IF ( do3d_compress )  THEN
379!
380!--       Compression, output of compression information on FLD-file and output
381!--       of compressed data.
382          CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, &
383                                 nzb, nz_do3d, prec )
384       ELSE
385!
386!--       Uncompressed output.
387#if defined( __parallel )
388          IF ( netcdf_output  .AND.  myid == 0 )  THEN
389             WRITE ( 30 )  simulated_time, do3d_time_count(av), av
390          ENDIF
391          WRITE ( 30 )  nxl-1, nxr+1, nys-1, nyn+1, nzb, nz_do3d
392          WRITE ( 30 )  local_pf
393#else
394          IF ( avs_output )  THEN
395             WRITE ( 30 )  local_pf(nxl:nxr+1,nys:nyn+1,:)
396          ENDIF
397#if defined( __netcdf )
398          IF ( netcdf_output )  THEN
399             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),       &
400                                  local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
401                                  start = (/ 1, 1, 1, do3d_time_count(av) /), &
402                                  count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
403             IF ( nc_stat /= NF90_NOERR)  CALL handle_netcdf_error( 1010 )
404          ENDIF
405#endif
406#endif
407       ENDIF
408
409       if = if + 1
410
411    ENDDO
412
413!
414!-- Deallocate temporary array.
415    DEALLOCATE( local_pf )
416
417
418    CALL cpu_log (log_point(14),'data_output_3d','stop','nobarrier')
419
420!
421!-- Formats.
4223300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/ &
423             'label = ',A,A)
424
425 END SUBROUTINE data_output_3d
Note: See TracBrowser for help on using the repository browser.