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

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

more preliminary uncomplete changes for ocean version

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