source: palm/trunk/SOURCE/data_output_dvrp.f90 @ 170

Last change on this file since 170 was 139, checked in by raasch, 16 years ago

New:
---

Plant canopy model of Watanabe (2004,BLM 112,307-341) added.
It can be switched on by the inipar parameter plant_canopy.
The inipar parameter canopy_mode can be used to prescribe a
plant canopy type. The default case is a homogeneous plant
canopy. Heterogeneous distributions of the leaf area
density and the canopy drag coefficient can be defined in the
new routine user_init_plant_canopy (user_interface).
The inipar parameters lad_surface, lad_vertical_gradient and
lad_vertical_gradient_level can be used in order to
prescribe the vertical profile of leaf area density. The
inipar parameter drag_coefficient determines the canopy
drag coefficient.
Finally, the inipar parameter pch_index determines the
index of the upper boundary of the plant canopy.

Allow new case bc_uv_t = 'dirichlet_0' for channel flow.

For unknown variables (CASE DEFAULT) call new subroutine user_data_output_dvrp

Pressure boundary conditions for vertical walls added to the multigrid solver.
They are applied using new wall flag arrays (wall_flags_..) which are defined
for each grid level. New argument gls added to routine user_init_grid
(user_interface).

Frequence of sorting particles can be controlled with new particles_par
parameter dt_sort_particles. Sorting is moved from the SGS timestep loop in
advec_particles after the end of this loop.

advec_particles, check_parameters, data_output_dvrp, header, init_3d_model, init_grid, init_particles, init_pegrid, modules, package_parin, parin, plant_canopy_model, read_var_list, read_3d_binary, user_interface, write_var_list, write_3d_binary

Changed:


Redefine initial nzb_local as the actual total size of topography (later the
extent of topography in nzb_local is reduced by 1dx at the E topography walls
and by 1dy at the N topography walls to form the basis for nzb_s_inner);
for consistency redefine 'single_building' case.

Vertical profiles now based on nzb_s_inner; they are divided by
ngp_2dh_s_inner (scalars, procucts of scalars) and ngp_2dh (staggered velocity
components and their products, procucts of scalars and velocity components),
respectively.

Allow two instead of one digit to specify isosurface and slicer variables.

Status of 3D-volume NetCDF data file only depends on switch netcdf_64bit_3d (check_open)

prognostic_equations include the respective wall_*flux in the parameter list of
calls of diffusion_s. Same as before, only the values of wall_heatflux(0:4)
can be assigned. At present, wall_humidityflux, wall_qflux, wall_salinityflux,
and wall_scalarflux are kept zero. diffusion_s uses the respective wall_*flux
instead of wall_heatflux. This update serves two purposes:

  • it avoids errors in calculations with humidity/scalar/salinity and prescribed

non-zero wall_heatflux,

  • it prepares PALM for a possible assignment of wall fluxes of

humidity/scalar/salinity in a future release.

buoyancy, check_open, data_output_dvrp, diffusion_s, diffusivities, flow_statistics, header, init_3d_model, init_dvrp, init_grid, modules, prognostic_equations

Errors:


Bugfix: summation of sums_l_l in diffusivities.

Several bugfixes in the ocean part: Initial density rho is calculated
(init_ocean). Error in initializing u_init and v_init removed
(check_parameters). Calculation of density flux now starts from
nzb+1 (production_e).

Bugfix: pleft/pright changed to pnorth/psouth in sendrecv of particle tail
numbers along y, small bugfixes in the SGS part (advec_particles)

Bugfix: model_string needed a default value (combine_plot_fields)

Bugfix: wavenumber calculation for even nx in routines maketri (poisfft)

Bugfix: assignment of fluxes at walls

Bugfix: absolute value of f must be used when calculating the Blackadar mixing length (init_1d_model)

advec_particles, check_parameters, combine_plot_fields, diffusion_s, diffusivities, init_ocean, init_1d_model, poisfft, production_e

  • Property svn:keywords set to Id
File size: 18.9 KB
Line 
1 MODULE dvrp_color
2
3    USE dvrp_variables
4
5    IMPLICIT NONE
6
7 CONTAINS
8
9    SUBROUTINE color_dvrp( value, color )
10
11       REAL, INTENT(IN)  ::  value
12       REAL, INTENT(OUT) ::  color(4)
13
14       REAL              ::  scale
15
16       scale = ( value - slicer_range_limits_dvrp(1,islice_dvrp) ) / &
17               ( slicer_range_limits_dvrp(2,islice_dvrp) -           &
18                 slicer_range_limits_dvrp(1,islice_dvrp) )
19
20       scale = MODULO( 180.0 + 180.0 * scale, 360.0 )
21
22       color = (/ scale, 0.5, 1.0, 0.0 /)
23
24    END SUBROUTINE color_dvrp
25
26 END MODULE dvrp_color
27
28
29 RECURSIVE SUBROUTINE data_output_dvrp
30
31!------------------------------------------------------------------------------!
32! Actual revisions:
33! -----------------
34!
35! TEST: different colours for isosurfaces
36! TEST: write statements
37!
38! Former revisions:
39! -----------------
40! $Id: data_output_dvrp.f90 139 2007-11-29 09:37:41Z raasch $
41!
42! 130 2007-11-13 14:08:40Z letzel
43! allow two instead of one digit to specify isosurface and slicer variables
44! for unknown variables (CASE DEFAULT) call new subroutine
45! user_data_output_dvrp
46!
47! 82 2007-04-16 15:40:52Z raasch
48! Preprocessor strings for different linux clusters changed to "lc",
49! routine local_flush is used for buffer flushing
50!
51! 75 2007-03-22 09:54:05Z raasch
52! Particles-package is now part of the default code,
53! moisture renamed humidity
54!
55! RCS Log replace by Id keyword, revision history cleaned up
56!
57! Revision 1.13  2006/02/23 10:25:12  raasch
58! Former routine plot_dvrp renamed data_output_dvrp,
59! Only a fraction of the particles may have a tail,
60! pl.. replaced by do.., %size renamed %dvrp_psize
61!
62! Revision 1.1  2000/04/27 06:27:17  raasch
63! Initial revision
64!
65!
66! Description:
67! ------------
68! Plot of isosurface, particles and slicers with dvrp-software
69!------------------------------------------------------------------------------!
70#if defined( __dvrp_graphics )
71
72    USE arrays_3d
73    USE cloud_parameters
74    USE cpulog
75    USE DVRP
76    USE dvrp_color
77    USE dvrp_variables
78    USE grid_variables
79    USE indices
80    USE interfaces
81    USE particle_attributes
82    USE pegrid
83    USE control_parameters
84
85    IMPLICIT NONE
86
87    CHARACTER (LEN=2) ::  section_chr
88    CHARACTER (LEN=6) ::  output_variable
89    INTEGER ::  i, j, k, l, m, n, nn, section_mode, tv, vn
90    INTEGER, DIMENSION(:), ALLOCATABLE ::  p_c, p_t
91    REAL    ::  center(3), distance, slicer_position, surface_value
92    REAL, DIMENSION(:),     ALLOCATABLE ::  psize, p_x, p_y, p_z
93    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  local_pf
94
95
96    WRITE ( 9, * ) '*** myid=', myid, ' Anfang data_output_dvrp'
97    CALL local_flush( 9 )
98    CALL cpu_log( log_point(27), 'data_output_dvrp', 'start' )
99
100!
101!-- Loop over all output modes choosed
102    m           = 1
103    tv          = 0  ! threshold counter
104    islice_dvrp = 0  ! slice plane counter
105    DO WHILE ( mode_dvrp(m) /= ' ' )
106!
107!--    Update of the steering variables
108       IF ( .NOT. lock_steering_update )  THEN
109!
110!--       Set lock to avoid recursive calls of DVRP_STEERING_UPDATE
111          lock_steering_update = .TRUE.
112!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: vor steering_update'
113!   CALL local_flush( 9 )
114          CALL DVRP_STEERING_UPDATE( m-1, data_output_dvrp )
115!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: nach steering_update'
116!   CALL local_flush( 9 )
117          lock_steering_update = .FALSE.
118       ENDIF
119
120!
121!--    Determine the variable which shall be plotted (in case of slicers or
122!--    isosurfaces)
123       IF ( mode_dvrp(m)(1:10) == 'isosurface' )  THEN
124          READ ( mode_dvrp(m), '(10X,I2)' )  vn
125          output_variable = do3d(0,vn)
126          tv = tv + 1
127       ELSEIF ( mode_dvrp(m)(1:6) == 'slicer' )  THEN
128          READ ( mode_dvrp(m), '(6X,I2)' )  vn
129          output_variable = do2d(0,vn)
130          l = MAX( 2, LEN_TRIM( do2d(0,vn) ) )
131          section_chr = do2d(0,vn)(l-1:l)
132          SELECT CASE ( section_chr )
133             CASE ( 'xy' )
134                section_mode = 2
135                slicer_position = zu(MIN( slicer_position_dvrp(m), nz_do3d ))
136             CASE ( 'xz' )
137                section_mode = 1
138                slicer_position = slicer_position_dvrp(m) * dy
139             CASE ( 'yz' )
140                section_mode = 0
141                slicer_position = slicer_position_dvrp(m) * dx
142          END SELECT
143       ENDIF
144
145!
146!--    Select the plot mode (in case of isosurface or slicer only if user has
147!--    defined a variable which shall be plotted; otherwise do nothing)
148       IF ( mode_dvrp(m)(1:9) == 'particles'  .AND.  particle_advection  .AND. &
149            simulated_time >= particle_advection_start )  THEN
150
151!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang particles'
152!   CALL local_flush( 9 )
153!
154!--       DVRP-Calls for plotting particles:
155          CALL cpu_log( log_point_s(28), 'dvrp_particles', 'start' )
156
157!
158!--       Definition of characteristics of particle material
159!          CALL DVRP_MATERIAL_RGB( m-1, 1, 0.1, 0.7, 0.1, 0.0 )
160          CALL DVRP_MATERIAL_RGB( m-1, 1, 0.0, 0.0, 0.0, 0.0 )
161
162!
163!--       Move particle coordinates to one-dimensional arrays
164          IF ( .NOT. use_particle_tails )  THEN
165!
166!--          All particles are output
167             ALLOCATE( psize(number_of_particles), p_t(number_of_particles), &
168                       p_c(number_of_particles), p_x(number_of_particles),   &
169                       p_y(number_of_particles), p_z(number_of_particles) )
170             psize = 0.0;  p_t = 0;  p_c = 0.0;  p_x = 0.0;  p_y = 0.0
171             p_z   = 0.0;
172             psize = particles(1:number_of_particles)%dvrp_psize
173             p_x   = particles(1:number_of_particles)%x * superelevation_x
174             p_y   = particles(1:number_of_particles)%y * superelevation_y
175             p_z   = particles(1:number_of_particles)%z * superelevation
176             p_c   = particles(1:number_of_particles)%color
177          ELSE
178!
179!--          Particles have a tail
180!            WRITE (9,*) '--- before ALLOCATE  simtime=',simulated_time,' #of_tails=', number_of_tails, &
181!                          ' max#of_tp=', maximum_number_of_tailpoints
182!   CALL local_flush( 9 )
183             ALLOCATE( psize(number_of_tails), p_t(number_of_tails),      &
184                       p_c(number_of_tails*maximum_number_of_tailpoints), &
185                       p_x(number_of_tails*maximum_number_of_tailpoints), &
186                       p_y(number_of_tails*maximum_number_of_tailpoints), &
187                       p_z(number_of_tails*maximum_number_of_tailpoints) )
188!            WRITE (9,*) '--- after ALLOCATE'
189!   CALL local_flush( 9 )
190             psize = 0.0;  p_t = 0;  p_c = 0.0;  p_x = 0.0;  p_y = 0.0
191             p_z   = 0.0;
192             i = 0
193             k = 0
194             DO  n = 1, number_of_particles
195                nn = particles(n)%tail_id
196                IF ( nn /= 0 )  THEN
197                   k = k + 1
198!                  IF ( simulated_time > 1338.0 )  THEN
199!                     WRITE (9,*) '--- particle ',n,' tail_id=',nn,' #of_tp=',particles(n)%tailpoints
200!   CALL local_flush( 9 )
201!                  ENDIF
202                   DO  j = 1, particles(n)%tailpoints
203                      i = i + 1
204                      p_x(i) = particle_tail_coordinates(j,1,nn) * &
205                                                                superelevation_x
206                      p_y(i) = particle_tail_coordinates(j,2,nn) * &
207                                                                superelevation_y
208                      p_z(i) = particle_tail_coordinates(j,3,nn) * &
209                                                                superelevation
210                      p_c(i) = particle_tail_coordinates(j,4,nn)
211!                     IF ( simulated_time > 1338.0 )  THEN
212!                        WRITE (9,*) '--- tp= ',i,' x=',p_x(i),' y=',p_y(i), &
213!                                                ' z=',p_z(i),' c=',p_c(i)
214!   CALL local_flush( 9 )
215!                     ENDIF
216                   ENDDO
217                   psize(k) = particles(n)%dvrp_psize
218                   p_t(k)   = particles(n)%tailpoints - 1
219!                  IF ( simulated_time > 1338.0 )  THEN
220!                     WRITE (9,*) '--- t= ',k,' psize=',psize(k),' p_t=',p_t(k)
221!   CALL local_flush( 9 )
222!                  ENDIF
223                ENDIF               
224             ENDDO
225!            WRITE (9,*) '--- after locally storing the particle attributes'
226!   CALL local_flush( 9 )
227          ENDIF
228
229!
230!--       Compute and plot particles in dvr-format
231          IF ( uniform_particles  .AND.  .NOT. use_particle_tails )  THEN
232!
233!--          All particles have the same color. Use simple routine to set
234!--          the particle attributes (produces less output data)
235             CALL DVRP_PARTICLES( m-1, p_x, p_y, p_z, psize )
236          ELSE
237!
238!--          Set color definitions
239             CALL user_dvrp_coltab( 'particles', 'none' )
240
241             CALL DVRP_COLORTABLE_HLS( m-1, 0, interval_values_dvrp,     &
242                                       interval_h_dvrp, interval_l_dvrp, &
243                                       interval_s_dvrp, interval_a_dvrp )
244
245             IF ( .NOT. use_particle_tails )  THEN
246                CALL DVRP_PARTICLES( m-1, number_of_particles, p_x, p_y, p_z, &
247                                     3, psize, p_c, p_t )
248             ELSE
249!               WRITE (9,*) '--- before DVRP_PARTICLES'
250!   CALL local_flush( 9 )
251                CALL DVRP_PARTICLES( m-1, number_of_tails, p_x, p_y, p_z, 15, &
252                                     psize, p_c, p_t )
253!               WRITE (9,*) '--- after DVRP_PARTICLES'
254!               WRITE (9,*) 'm-1 = ',m-1
255!               WRITE (9,*) 'number_of_tails=', number_of_tails
256!               WRITE (9,*) 'p_x =', p_x
257!               WRITE (9,*) 'p_y =', p_y
258!               WRITE (9,*) 'p_z =', p_z
259!               WRITE (9,*) 'psize =', psize
260!               WRITE (9,*) 'p_c =', p_c
261!               WRITE (9,*) 'p_t =', p_t
262
263!   CALL local_flush( 9 )
264             ENDIF
265          ENDIF
266
267          CALL DVRP_VISUALIZE( m-1, 3, dvrp_filecount )
268!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende particles'
269!   CALL local_flush( 9 )
270
271          DEALLOCATE( psize, p_c, p_t, p_x, p_y, p_z )
272
273          CALL cpu_log( log_point_s(28), 'dvrp_particles', 'stop' )
274
275
276       ELSEIF ( ( mode_dvrp(m)(1:10) == 'isosurface'  .OR.   &
277                  mode_dvrp(m)(1:6)  == 'slicer'           ) &
278                  .AND.  output_variable /= ' ' )  THEN
279
280!
281!--       Create an intermediate array, properly dimensioned for plot-output
282          ALLOCATE( local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d) )
283
284!
285!--       Move original array to intermediate array
286          SELECT CASE ( output_variable )
287
288             CASE ( 'u', 'u_xy', 'u_xz', 'u_yz' )
289                DO  i = nxl, nxr+1
290                   DO  j = nys, nyn+1
291                      DO  k = nzb, nz_do3d
292                         local_pf(i,j,k) = u(k,j,i)
293                      ENDDO
294                   ENDDO
295                ENDDO
296!
297!--             Replace mirrored values at lower surface by real surface values
298                IF ( output_variable == 'u_xz'  .OR. &
299                     output_variable == 'u_yz' )  THEN
300                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
301                ENDIF
302
303
304             CASE ( 'v', 'v_xy', 'v_xz', 'v_yz' )
305                DO  i = nxl, nxr+1
306                   DO  j = nys, nyn+1
307                      DO  k = nzb, nz_do3d
308                         local_pf(i,j,k) = v(k,j,i)
309                      ENDDO
310                   ENDDO
311                ENDDO
312!
313!--             Replace mirrored values at lower surface by real surface values
314                IF ( output_variable == 'v_xz'  .OR. &
315                     output_variable == 'v_yz' )  THEN
316                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
317                ENDIF
318
319             CASE ( 'w', 'w_xy', 'w_xz', 'w_yz' )
320                DO  i = nxl, nxr+1
321                   DO  j = nys, nyn+1
322                      DO  k = nzb, nz_do3d
323                         local_pf(i,j,k) = w(k,j,i)
324                      ENDDO
325                   ENDDO
326                ENDDO
327! Averaging for Langmuir circulation
328!                DO  k = nzb, nz_do3d
329!                   DO  j = nys+1, nyn
330!                      DO  i = nxl, nxr+1
331!                         local_pf(i,j,k) = 0.25 * local_pf(i,j-1,k) + &
332!                                           0.50 * local_pf(i,j,k)   + &
333!                                           0.25 * local_pf(i,j+1,k)
334!                      ENDDO
335!                   ENDDO
336!                ENDDO
337
338             CASE ( 'p', 'p_xy', 'p_xz', 'p_yz' )
339                DO  i = nxl, nxr+1
340                   DO  j = nys, nyn+1
341                      DO  k = nzb, nz_do3d
342                         local_pf(i,j,k) = p(k,j,i)
343                      ENDDO
344                   ENDDO
345                ENDDO
346
347             CASE ( 'pt', 'pt_xy', 'pt_xz', 'pt_yz' )
348                IF ( .NOT. cloud_physics ) THEN
349                   DO  i = nxl, nxr+1
350                      DO  j = nys, nyn+1
351                         DO  k = nzb, nz_do3d
352                            local_pf(i,j,k) = pt(k,j,i)
353                         ENDDO
354                      ENDDO
355                   ENDDO
356                ELSE
357                   DO  i = nxl, nxr+1
358                      DO  j = nys, nyn+1
359                         DO  k = nzb, nz_do3d
360                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp * pt_d_t(k) * &
361                                                          ql(k,j,i)
362                         ENDDO
363                      ENDDO
364                   ENDDO
365                ENDIF
366
367             CASE ( 'q', 'q_xy', 'q_xz', 'q_yz' )
368                IF ( humidity  .OR.  passive_scalar )  THEN
369                   DO  i = nxl, nxr+1
370                      DO  j = nys, nyn+1
371                         DO  k = nzb, nz_do3d
372                            local_pf(i,j,k) = q(k,j,i)
373                         ENDDO
374                      ENDDO
375                   ENDDO           
376                ELSE
377                   IF ( myid == 0 )  THEN
378                      PRINT*, '+++ data_output_dvrp: if humidity/passive_scalar = ', & 
379                              'FALSE output of ', output_variable,            &
380                              'is not provided' 
381                   ENDIF
382                ENDIF
383             
384             CASE ( 'ql', 'ql_xy', 'ql_xz', 'ql_yz' )
385                IF ( cloud_physics  .OR.  cloud_droplets )  THEN
386                   DO  i = nxl, nxr+1
387                      DO  j = nys, nyn+1
388                         DO  k = nzb, nz_do3d
389                            local_pf(i,j,k) = ql(k,j,i)
390                         ENDDO
391                      ENDDO
392                   ENDDO
393                ELSE
394                   IF ( myid == 0 ) THEN
395                      PRINT*, '+++ data_output_dvrp: if cloud_physics = FALSE ', & 
396                              'output of ', output_variable, 'is not provided' 
397                   ENDIF
398                ENDIF
399
400             CASE ( 'u*_xy' )
401                DO  i = nxl, nxr+1
402                   DO  j = nys, nyn+1
403                      local_pf(i,j,nzb+1) = us(j,i)
404                   ENDDO
405                ENDDO
406                slicer_position = zu(nzb+1)
407
408             CASE ( 't*_xy' )
409                DO  i = nxl, nxr+1
410                   DO  j = nys, nyn+1
411                      local_pf(i,j,nzb+1) = ts(j,i)
412                   ENDDO
413                ENDDO
414                slicer_position = zu(nzb+1)
415
416
417             CASE DEFAULT
418!
419!--             The DEFAULT case is reached either if output_variable contains
420!--             unsupported variable or if the user has coded a special case in
421!--             the user interface. There, the subroutine user_data_output_dvrp
422!--             checks which of these two conditions applies.
423                CALL user_data_output_dvrp( output_variable, local_pf )
424
425
426          END SELECT
427
428
429          IF ( mode_dvrp(m)(1:10) == 'isosurface' )  THEN
430
431!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang isosurface'
432!   CALL local_flush( 9 )
433!
434!--          DVRP-Calls for plotting isosurfaces:
435             CALL cpu_log( log_point_s(26), 'dvrp_isosurface', 'start' )
436
437!
438!--          Definition of characteristics of isosurface material
439!--          Preliminary settings for w!
440             IF ( output_variable == 'w' )  THEN
441                IF ( tv == 1 )  THEN
442                   CALL DVRP_MATERIAL_RGB( m-1, 1, 0.8, 0.1, 0.1, 0.0 )
443                ELSE
444                   CALL DVRP_MATERIAL_RGB( m-1, 1, 0.1, 0.1, 0.8, 0.0 )
445                ENDIF
446             ELSE
447                CALL DVRP_MATERIAL_RGB( m-1, 1, 0.9, 0.9, 0.9, 0.0 )
448             ENDIF
449
450!
451!--          Compute and plot isosurface in dvr-format
452             CALL DVRP_DATA( m-1, local_pf, 1, nx_dvrp, ny_dvrp, nz_dvrp, &
453                             cyclic_dvrp, cyclic_dvrp, cyclic_dvrp )
454             CALL DVRP_THRESHOLD( m-1, threshold(tv) )
455             CALL DVRP_VISUALIZE( m-1, 1, dvrp_filecount )
456!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende isosurface'
457!   CALL local_flush( 9 )
458
459             CALL cpu_log( log_point_s(26), 'dvrp_isosurface', 'stop' )
460
461          ELSEIF ( mode_dvrp(m)(1:6) == 'slicer' )  THEN
462
463!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang slicer'
464!   CALL local_flush( 9 )
465!
466!--          DVRP-Calls for plotting slicers:
467             CALL cpu_log( log_point_s(27), 'dvrp_slicer', 'start' )
468
469!
470!--          Material and color definitions
471             CALL DVRP_MATERIAL_RGB( m-1, 1, 0.0, 0.0, 0.0, 0.0 )
472
473             islice_dvrp = islice_dvrp + 1
474!             CALL DVRP_COLORFUNCTION( m-1, DVRP_CM_HLS, 25,                    &
475!                                      slicer_range_limits_dvrp(:,islice_dvrp), &
476!                                      color_dvrp )
477
478             CALL user_dvrp_coltab( 'slicer', output_variable )
479
480             CALL DVRP_COLORTABLE_HLS( m-1, 1, interval_values_dvrp,     &
481                                       interval_h_dvrp, interval_l_dvrp, &
482                                       interval_s_dvrp, interval_a_dvrp )
483
484!
485!--          Compute and plot slicer in dvr-format
486             CALL DVRP_DATA( m-1, local_pf, 1, nx_dvrp, ny_dvrp, nz_dvrp, &
487                             cyclic_dvrp, cyclic_dvrp, cyclic_dvrp )
488!             CALL DVRP_SLICER( m-1, section_mode, slicer_position )
489             CALL DVRP_SLICER( m-1, 2, 1.0 )
490             WRITE (9,*) 'nx_dvrp=', nx_dvrp
491             WRITE (9,*) 'ny_dvrp=', ny_dvrp
492             WRITE (9,*) 'nz_dvrp=', nz_dvrp
493             WRITE (9,*) 'section_mode=', section_mode
494             WRITE (9,*) 'slicer_position=', slicer_position
495             CALL local_flush( 9 )
496
497             CALL DVRP_VISUALIZE( m-1, 2, dvrp_filecount )
498
499             CALL cpu_log( log_point_s(27), 'dvrp_slicer', 'stop' )
500
501!   WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende slicer'
502!   CALL local_flush( 9 )
503          ENDIF
504
505          DEALLOCATE( local_pf )
506
507       ENDIF
508
509       m = m + 1
510
511    ENDDO
512
513    dvrp_filecount = dvrp_filecount + 1
514
515    CALL cpu_log( log_point(27), 'data_output_dvrp', 'stop' )
516!   WRITE ( 9, * ) '*** myid=', myid, ' Ende data_output_dvrp'
517!   CALL local_flush( 9 )
518
519#endif
520 END SUBROUTINE data_output_dvrp
Note: See TracBrowser for help on using the repository browser.