source: palm/trunk/SOURCE/init_dvrp.f90 @ 14

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

flush calls adjusted

  • Property svn:keywords set to Id
File size: 22.0 KB
Line 
1  SUBROUTINE init_dvrp
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Test output of isosurface on camera file
7! TEST: print* statements
8! ToDo: checking of mode_dvrp for legal values is not correct
9!
10! Former revisions:
11! -----------------
12! $Id: init_dvrp.f90 13 2007-02-14 12:15:07Z raasch $
13! RCS Log replace by Id keyword, revision history cleaned up
14!
15! Revision 1.12  2006/02/23 12:30:22  raasch
16! ebene renamed section, pl.. replaced by do..,
17!
18! Revision 1.1  2000/04/27 06:24:39  raasch
19! Initial revision
20!
21!
22! Description:
23! ------------
24! Initializing actions needed when using dvrp-software
25!------------------------------------------------------------------------------!
26#if defined( __dvrp_graphics )
27
28    USE arrays_3d
29    USE DVRP
30    USE dvrp_variables
31    USE grid_variables
32    USE indices
33    USE pegrid
34    USE control_parameters
35
36    IMPLICIT NONE
37
38    CHARACTER (LEN=2)  ::  section_chr
39    CHARACTER (LEN=80) ::  dvrp_file_local
40    INTEGER ::  i, j, k, l, m, pn, tv, vn
41    LOGICAL ::  allocated
42    REAL    ::  center(3), distance
43
44    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  local_pf
45
46    TYPE(CSTRING), SAVE ::  dvrp_directory_c, dvrp_file_c, &
47                            dvrp_file_local_c,dvrp_host_c, &
48                            dvrp_password_c, dvrp_username_c, name_c
49
50!
51!-- Set the maximum time the program can be suspended on user request (by
52!-- dvrp steering). This variable is defined in module DVRP.
53    DVRP_MAX_SUSPEND_TIME = 7200
54
55!
56!-- Allocate array holding the names and limits of the steering variables
57!-- (must have the same number of elements as array mode_dvrp!)
58    ALLOCATE( steering_dvrp(10) )
59
60!
61!-- Check, if output parameters are given and/or allowed
62!-- and set default-values, where necessary
63    IF ( dvrp_username == ' ' )  THEN
64       IF ( myid == 0 )  THEN
65          PRINT*, '+++ init_dvrp: dvrp_username is undefined'
66          CALL local_stop
67       ENDIF
68    ENDIF
69
70    IF ( dvrp_output /= 'ftp'  .AND.  dvrp_output /= 'rtsp'  .AND. &
71         dvrp_output /= 'local' )  THEN
72       IF ( myid == 0 )  THEN
73          PRINT*, '+++ init_dvrp: dvrp_output="', dvrp_output, '" not allowed'
74          CALL local_stop
75       ENDIF
76    ENDIF
77
78    IF ( dvrp_directory == 'default' )  THEN
79       dvrp_directory = TRIM( dvrp_username ) // '/' // TRIM( run_identifier )
80    ENDIF
81
82    IF ( dvrp_output /= 'local' )  THEN
83       IF ( dvrp_file /= 'default'  .AND.  dvrp_file /= '/dev/null' )  THEN
84          IF ( myid == 0 )  THEN
85             PRINT*, '+++ init_dvrp: dvrp_file="', dvrp_file, '" not allowed'
86             CALL local_stop
87          ENDIF
88       ENDIF
89    ENDIF
90
91!
92!-- Strings are assigned to strings of special type which have a CHAR( 0 )
93!-- (C end-of-character symbol) at their end. This is needed when strings are
94!-- passed to C routines.
95    dvrp_directory_c = dvrp_directory
96    dvrp_file_c      = dvrp_file
97    dvrp_host_c      = dvrp_host
98    dvrp_password_c  = dvrp_password
99    dvrp_username_c  = dvrp_username
100
101!
102!-- Loop over all output modes choosed
103    m = 1
104    allocated = .FALSE.
105    DO WHILE ( mode_dvrp(m) /= ' ' )
106   
107!
108!--    Check, if mode is allowed
109       IF ( mode_dvrp(m)(1:10) /= 'isosurface'  .AND. &
110            mode_dvrp(m)(1:6)  /= 'slicer'      .AND. &
111            mode_dvrp(m)(1:9)  /= 'particles' )  THEN
112
113          IF ( myid == 0 )  THEN
114             PRINT*, '+++ init_dvrp: mode_dvrp="', mode_dvrp, '" not allowed'
115          ENDIF
116          CALL local_stop
117
118       ENDIF
119   
120!
121!--    Camera position must be computed and written on file when no dvrp-output
122!--    has been generated so far (in former runs)
123!       IF ( dvrp_filecount == 0 )  THEN
124!
125!--       Compute center of domain and distance of camera from center
126          center(1) = ( nx + 1.0 ) * dx * 0.5 * superelevation_x
127          center(2) = ( ny + 1.0 ) * dy * 0.5 * superelevation_y
128          center(3) = ( zu(nz_do3d) - zu(nzb) ) * 0.5 * superelevation
129          distance  = 1.5 * MAX( ( nx + 1.0 ) * dx * superelevation_x, &
130                                 ( ny + 1.0 ) * dy * superelevation_y, &
131                                 ( zu(nz_do3d) - zu(nzb) ) * superelevation )
132
133!
134!--       Write camera position on file
135          CALL DVRP_INIT( m-1, 0 )
136
137!
138!--       Create filename for camera
139          IF ( dvrp_output == 'rtsp' )  THEN
140
141    WRITE ( 9, * ) '***  vor dvrp_output_rtsp'
142#if defined( __ibm )
143    CALL FLUSH_( 9 )
144#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
145    CALL FLUSH( 9 )
146#endif
147
148             dvrp_file   = TRIM( mode_dvrp(m) ) // '/camera.dvr'
149             dvrp_file_c = dvrp_file
150             CALL DVRP_OUTPUT_RTSP( m-1, dvrp_host_c, dvrp_username_c, &
151                                    dvrp_password_c, dvrp_directory_c, &
152                                    dvrp_file_c )
153    WRITE ( 9, * ) '***  nach dvrp_output_rtsp'
154#if defined( __ibm )
155    CALL FLUSH_( 9 )
156#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
157    CALL FLUSH( 9 )
158#endif
159
160          ELSEIF ( dvrp_output == 'ftp' )  THEN
161
162             dvrp_file   = TRIM( mode_dvrp(m) ) // '.camera.dvr'
163             dvrp_file_c = dvrp_file
164!             CALL DVRP_OUTPUT_FTP( m-1, 0, dvrp_host_c, dvrp_username_c, &
165!                                   dvrp_password_c, dvrp_directory_c,    &
166!                                   dvrp_file_c )
167
168          ELSE
169
170             IF ( dvrp_file(1:9) /= '/dev/null' )  THEN
171                dvrp_file_local   = TRIM( mode_dvrp(m) ) // '.camera.dvr'
172                dvrp_file_local_c = dvrp_file_local
173             ELSE
174                dvrp_file_local_c = dvrp_file_c
175             ENDIF
176             CALL DVRP_OUTPUT_LOCAL( m-1, 0, dvrp_file_local_c )
177
178          ENDIF
179
180          CALL DVRP_CAMERA( m-1, center, distance )
181    WRITE ( 9, * ) '***  #1'
182#if defined( __ibm )
183    CALL FLUSH_( 9 )
184#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
185    CALL FLUSH( 9 )
186#endif
187
188!
189!--       Define bounding box material and create a bounding box
190          CALL DVRP_MATERIAL_RGB( m-1, 1, 0.5, 0.5, 0.5, 0.0 )
191          CALL DVRP_BOUNDINGBOX( m-1, 1, 0.01, 0.0, 0.0, 0.0,    &
192                                 (nx+1) * dx * superelevation_x, &
193                                 (ny+1) * dy * superelevation_y, &
194                                 zu(nz_do3d) * superelevation )
195
196          CALL DVRP_VISUALIZE( m-1, 0, 0 )
197          CALL DVRP_EXIT( m-1 )
198    WRITE ( 9, * ) '***  #2'
199#if defined( __ibm )
200    CALL FLUSH_( 9 )
201#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
202    CALL FLUSH( 9 )
203#endif
204
205
206!
207!--       Write topography isosurface on file
208          CALL DVRP_INIT( m-1, 0 )
209
210!
211!--       Create filename for buildings
212          IF ( dvrp_output == 'rtsp' )  THEN
213
214             dvrp_file   = TRIM( mode_dvrp(m) ) // '/buildings.dvr'
215             dvrp_file_c = dvrp_file
216             CALL DVRP_OUTPUT_RTSP( m-1, dvrp_host_c, dvrp_username_c, &
217                                    dvrp_password_c, dvrp_directory_c, &
218                                    dvrp_file_c )
219    WRITE ( 9, * ) '***  #3'
220#if defined( __ibm )
221    CALL FLUSH_( 9 )
222#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
223    CALL FLUSH( 9 )
224#endif
225
226          ENDIF
227
228!
229!--       Determine local gridpoint coordinates
230          IF ( .NOT. allocated )  THEN
231             ALLOCATE( xcoor_dvrp(nxl:nxr+1), ycoor_dvrp(nys:nyn+1), &
232                       zcoor_dvrp(nzb:nz_do3d) )
233             allocated = .TRUE.
234
235             DO  i = nxl, nxr+1
236                xcoor_dvrp(i) = i * dx * superelevation_x
237             ENDDO
238             DO  j = nys, nyn+1
239                ycoor_dvrp(j) = j * dy * superelevation_y
240             ENDDO
241             zcoor_dvrp = zu(nzb:nz_do3d) * superelevation
242             nx_dvrp    = nxr+1 - nxl + 1
243             ny_dvrp    = nyn+1 - nys + 1
244             nz_dvrp    = nz_do3d - nzb + 1
245          ENDIF
246
247!
248!--       Define the grid used by dvrp
249          CALL DVRP_GRID( m-1, nx_dvrp, ny_dvrp, nz_dvrp, xcoor_dvrp, &
250                          ycoor_dvrp, zcoor_dvrp )
251          CALL DVRP_MATERIAL_RGB( m-1, 1, 0.8, 0.7, 0.6, 0.0 )
252    WRITE ( 9, * ) '***  #4'
253#if defined( __ibm )
254    CALL FLUSH_( 9 )
255#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
256    CALL FLUSH( 9 )
257#endif
258
259!
260!--       Compute and plot isosurface in dvr-format
261          ALLOCATE( local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d) )
262          local_pf = 0.0
263          DO  i = nxl, nxr+1
264             DO  j = nys, nyn+1
265                IF ( nzb_s_inner(j,i) > 0 )  THEN
266                      local_pf(i,j,nzb:nzb_s_inner(j,i)) = 1.0
267                   ENDIF
268             ENDDO
269          ENDDO
270    WRITE ( 9, * ) '***  #4.1'
271#if defined( __ibm )
272    CALL FLUSH_( 9 )
273#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
274    CALL FLUSH( 9 )
275#endif
276          CALL DVRP_DATA( m-1, local_pf, 1, nx_dvrp, ny_dvrp, nz_dvrp, &
277                          cyclic_dvrp, cyclic_dvrp, cyclic_dvrp )
278    WRITE ( 9, * ) '***  #4.2'
279#if defined( __ibm )
280    CALL FLUSH_( 9 )
281#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
282    CALL FLUSH( 9 )
283#endif
284          CALL DVRP_THRESHOLD( m-1, 1.0 )
285    WRITE ( 9, * ) '***  #4.3'
286#if defined( __ibm )
287    CALL FLUSH_( 9 )
288#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
289    CALL FLUSH( 9 )
290#endif
291          CALL DVRP_VISUALIZE( m-1, 1, 0 )
292    WRITE ( 9, * ) '***  #4.4'
293#if defined( __ibm )
294    CALL FLUSH_( 9 )
295#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
296    CALL FLUSH( 9 )
297#endif
298
299          DEALLOCATE( local_pf )
300
301          CALL DVRP_EXIT( m-1 )
302    WRITE ( 9, * ) '***  #5'
303#if defined( __ibm )
304    CALL FLUSH_( 9 )
305#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
306    CALL FLUSH( 9 )
307#endif
308
309!
310!--       Write the surface isosurface on file
311          CALL DVRP_INIT( m-1, 0 )
312
313!
314!--       Create filename for surface
315          IF ( dvrp_output == 'rtsp' )  THEN
316
317             dvrp_file   = TRIM( mode_dvrp(m) ) // '/surface.dvr'
318             dvrp_file_c = dvrp_file
319             CALL DVRP_OUTPUT_RTSP( m-1, dvrp_host_c, dvrp_username_c, &
320                                    dvrp_password_c, dvrp_directory_c, &
321                                    dvrp_file_c )
322    WRITE ( 9, * ) '***  #6'
323#if defined( __ibm )
324    CALL FLUSH_( 9 )
325#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
326    CALL FLUSH( 9 )
327#endif
328
329          ENDIF
330
331!
332!--       Determine local gridpoint coordinates
333          IF ( .NOT. allocated )  THEN
334             ALLOCATE( xcoor_dvrp(nxl:nxr+1), ycoor_dvrp(nys:nyn+1), &
335                       zcoor_dvrp(nzb:nz_do3d) )
336             allocated = .TRUE.
337
338             DO  i = nxl, nxr+1
339                xcoor_dvrp(i) = i * dx * superelevation_x
340             ENDDO
341             DO  j = nys, nyn+1
342                ycoor_dvrp(j) = j * dy * superelevation_y
343             ENDDO
344             zcoor_dvrp = zu(nzb:nz_do3d) * superelevation
345             nx_dvrp    = nxr+1 - nxl + 1
346             ny_dvrp    = nyn+1 - nys + 1
347             nz_dvrp    = nz_do3d - nzb + 1
348          ENDIF
349
350!
351!--       Define the grid used by dvrp
352          CALL DVRP_GRID( m-1, nx_dvrp, ny_dvrp, nz_dvrp, xcoor_dvrp, &
353                          ycoor_dvrp, zcoor_dvrp )
354          CALL DVRP_MATERIAL_RGB( m-1, 1, 0.0, 0.6, 0.0, 0.0 )
355    WRITE ( 9, * ) '***  #7'
356#if defined( __ibm )
357    CALL FLUSH_( 9 )
358#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
359    CALL FLUSH( 9 )
360#endif
361
362!
363!--       Compute and plot isosurface in dvr-format
364          ALLOCATE( local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d) )
365          local_pf = 0.0
366          local_pf(:,:,0) = 1.0
367
368          CALL DVRP_DATA( m-1, local_pf, 1, nx_dvrp, ny_dvrp, nz_dvrp, &
369                          cyclic_dvrp, cyclic_dvrp, cyclic_dvrp )
370          CALL DVRP_THRESHOLD( m-1, 1.0 )
371          CALL DVRP_VISUALIZE( m-1, 1, 0 )
372
373          DEALLOCATE( local_pf )
374
375          CALL DVRP_EXIT( m-1 )
376    WRITE ( 9, * ) '***  #8'
377#if defined( __ibm )
378    CALL FLUSH_( 9 )
379#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
380    CALL FLUSH( 9 )
381#endif
382
383   
384!       ENDIF
385
386
387!
388!--    Initialize dvrp for all dvrp-calls during the run
389       CALL DVRP_INIT( m-1, 0 )
390
391!
392!--    Preliminary definition of filename for dvrp-output
393       IF ( dvrp_output == 'rtsp' )  THEN
394
395!
396!--       First initialize parameters for possible interactive steering.
397!--       Every parameter has to be passed to the respective stream.
398          pn = 1
399!
400!--       Initialize threshold counter needed for initialization of the
401!--       isosurface steering variables
402          tv = 0
403
404          DO WHILE ( mode_dvrp(pn) /= ' ' )
405
406             IF ( mode_dvrp(pn)(1:10) == 'isosurface' )  THEN
407
408                READ ( mode_dvrp(pn), '(10X,I1)' )  vn
409                steering_dvrp(pn)%name = do3d(0,vn)
410                tv = tv + 1
411
412                IF ( do3d(0,vn)(1:1) == 'w' )  THEN
413                   steering_dvrp(pn)%min  = -4.0
414                   steering_dvrp(pn)%max  =  5.0
415                ELSE
416                   steering_dvrp(pn)%min  = 288.0
417                   steering_dvrp(pn)%max  = 292.0
418                ENDIF
419
420                name_c = TRIM( do3d(0,vn) )
421    WRITE ( 9, * ) '***  #9'
422#if defined( __ibm )
423    CALL FLUSH_( 9 )
424#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
425    CALL FLUSH( 9 )
426#endif
427                CALL DVRP_STEERING_INIT( m-1, name_c, steering_dvrp(pn)%min, &
428                                         steering_dvrp(pn)%max, threshold(tv) )
429    WRITE ( 9, * ) '***  #10'
430#if defined( __ibm )
431    CALL FLUSH_( 9 )
432#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
433    CALL FLUSH( 9 )
434#endif
435
436             ELSEIF ( mode_dvrp(pn)(1:6) == 'slicer' )  THEN
437
438                READ ( mode_dvrp(pn), '(6X,I1)' )  vn
439                steering_dvrp(pn)%name = do2d(0,vn)
440                name_c = TRIM( do2d(0,vn) )
441
442                l = MAX( 2, LEN_TRIM( do2d(0,vn) ) )
443                section_chr = do2d(0,vn)(l-1:l)
444                SELECT CASE ( section_chr )
445                   CASE ( 'xy' )
446                      steering_dvrp(pn)%imin   = 0
447                      steering_dvrp(pn)%imax   = nz_do3d
448                      slicer_position_dvrp(pn) = section(1,1)
449                      CALL DVRP_STEERING_INIT( m-1, name_c,            &
450                                               steering_dvrp(pn)%imin, &
451                                               steering_dvrp(pn)%imax, &
452                                               slicer_position_dvrp(pn) )
453                   CASE ( 'xz' )
454                      steering_dvrp(pn)%imin   = 0
455                      steering_dvrp(pn)%imax   = ny
456                      slicer_position_dvrp(pn) = section(1,2)
457                      CALL DVRP_STEERING_INIT( m-1, name_c,            &
458                                               steering_dvrp(pn)%imin, &
459                                               steering_dvrp(pn)%imax, &
460                                               slicer_position_dvrp(pn) )
461                   CASE ( 'yz' )
462                      steering_dvrp(pn)%imin = 0
463                      steering_dvrp(pn)%imax = nx
464                      slicer_position_dvrp(pn) = section(1,3)
465                      CALL DVRP_STEERING_INIT( m-1, name_c,            &
466                                               steering_dvrp(pn)%imin, &
467                                               steering_dvrp(pn)%imax, &
468                                               slicer_position_dvrp(pn) )
469                END SELECT
470
471             ENDIF
472
473             pn = pn + 1
474
475          ENDDO
476
477    WRITE ( 9, * ) '***  #11'
478#if defined( __ibm )
479    CALL FLUSH_( 9 )
480#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
481    CALL FLUSH( 9 )
482#endif
483
484          dvrp_file = TRIM( mode_dvrp(m) ) // '/*****.dvr'
485          dvrp_file_c = dvrp_file
486          CALL DVRP_OUTPUT_RTSP( m-1, dvrp_host_c, dvrp_username_c, &
487                                 dvrp_password_c, dvrp_directory_c, &
488                                 dvrp_file_c )
489    WRITE ( 9, * ) '***  #12'
490#if defined( __ibm )
491    CALL FLUSH_( 9 )
492#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
493    CALL FLUSH( 9 )
494#endif
495
496       ELSEIF ( dvrp_output == 'ftp' )  THEN
497
498          dvrp_file   = TRIM( mode_dvrp(m) ) // '.%05d.dvr'
499          dvrp_file_c = dvrp_file
500!          CALL DVRP_OUTPUT_FTP( m-1, 0, dvrp_host_c, dvrp_username_c, &
501!                                dvrp_password_c, dvrp_directory_c, dvrp_file_c )
502
503       ELSE
504
505          IF ( dvrp_file(1:9) /= '/dev/null' )  THEN
506             dvrp_file_local   = TRIM( mode_dvrp(m) ) // '_%05d.dvr'
507             dvrp_file_local_c = dvrp_file_local
508          ELSE
509             dvrp_file_local_c = dvrp_file_c
510          ENDIF
511          CALL DVRP_OUTPUT_LOCAL( m-1, 0, dvrp_file_local_c )
512
513       ENDIF
514
515!       dvrp_file = TRIM( mode_dvrp(m) ) // '.%05d.dvr' // CHAR( 0 )
516!       dvrp_file = TRIM( mode_dvrp(m) ) // '/*****.dvr' // CHAR( 0 )
517!       dvrp_file = '/dev/null' // CHAR( 0 )
518!       CALL DVRP_OUTPUT_FTP( m-1, 0, dvrp_host, dvrp_username, dvrp_password, &
519!                             dvrp_directory, dvrp_file )
520!       CALL DVRP_OUTPUT_RTSP( m-1, dvrp_host, dvrp_username, dvrp_password, &
521!                              dvrp_directory, dvrp_file )
522!       CALL DVRP_OUTPUT_LOCAL( m-1, 0, dvrp_file )
523
524!
525!--    Determine local gridpoint coordinates
526       IF ( .NOT. allocated )  THEN
527          ALLOCATE( xcoor_dvrp(nxl:nxr+1), ycoor_dvrp(nys:nyn+1), &
528                    zcoor_dvrp(nzb:nz_do3d) )
529          allocated = .TRUE.
530
531          DO  i = nxl, nxr+1
532             xcoor_dvrp(i) = i * dx * superelevation_x
533          ENDDO
534          DO  j = nys, nyn+1
535             ycoor_dvrp(j) = j * dy * superelevation_y
536          ENDDO
537          zcoor_dvrp = zu(nzb:nz_do3d) * superelevation
538          nx_dvrp    = nxr+1 - nxl + 1
539          ny_dvrp    = nyn+1 - nys + 1
540          nz_dvrp    = nz_do3d - nzb + 1
541       ENDIF
542
543!
544!--    Define the grid used by dvrp
545    WRITE ( 9, * ) '***  #13'
546#if defined( __ibm )
547    CALL FLUSH_( 9 )
548#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
549    CALL FLUSH( 9 )
550#endif
551
552       CALL DVRP_GRID( m-1, nx_dvrp, ny_dvrp, nz_dvrp, xcoor_dvrp, ycoor_dvrp, &
553                       zcoor_dvrp )
554    WRITE ( 9, * ) '***  #14'
555#if defined( __ibm )
556    CALL FLUSH_( 9 )
557#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
558    CALL FLUSH( 9 )
559#endif
560
561
562       m = m + 1
563
564    ENDDO
565
566#endif
567 END SUBROUTINE init_dvrp
568
569 
570 SUBROUTINE init_dvrp_logging
571
572!------------------------------------------------------------------------------!
573! Description:
574! ------------
575! Initializes logging events for time measurement with dvrp software
576! and splits one PE from the global communicator in case that dvrp output
577! shall be done by one single PE.
578!------------------------------------------------------------------------------!
579#if defined( __dvrp_graphics )
580
581    USE dvrp_variables
582    USE pegrid
583
584    IMPLICIT NONE
585
586    CHARACTER (LEN=4) ::  chr
587    INTEGER           ::  idummy
588
589!
590!-- Initialize logging of calls by DVRP graphic software
591    WRITE ( 9, * ) '*** myid=', myid, ' vor DVRP_LOG_INIT'
592#if defined( __ibm )
593    CALL FLUSH_( 9 )
594#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
595    CALL FLUSH( 9 )
596#endif
597    CALL DVRP_LOG_INIT( 'DVRP_LOG' // CHAR( 0 ), 0 )
598    WRITE ( 9, * ) '*** myid=', myid, ' nach DVRP_LOG_INIT'
599#if defined( __ibm )
600    CALL FLUSH_( 9 )
601#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
602    CALL FLUSH( 9 )
603#endif
604
605!
606!-- User-defined logging events: #1 (total time needed by PALM)
607    WRITE ( 9, * ) '*** myid=', myid, ' vor DVRP_LOG_SYMBOL'
608#if defined( __ibm )
609    CALL FLUSH_( 9 )
610#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
611    CALL FLUSH( 9 )
612#endif
613    CALL DVRP_LOG_SYMBOL( 1, 'PALM_total' // CHAR( 0 ) )
614    WRITE ( 9, * ) '*** myid=', myid, ' nach DVRP_LOG_SYMBOL'
615#if defined( __ibm )
616    CALL FLUSH_( 9 )
617#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
618    CALL FLUSH( 9 )
619#endif
620    CALL DVRP_LOG_SYMBOL( 2, 'PALM_timestep' // CHAR( 0 ) )
621    WRITE ( 9, * ) '*** myid=', myid, ' vor DVRP_LOG_EVENT'
622#if defined( __ibm )
623    CALL FLUSH_( 9 )
624#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
625    CALL FLUSH( 9 )
626#endif
627    CALL DVRP_LOG_EVENT( 1, 1 )
628    WRITE ( 9, * ) '*** myid=', myid, ' nach DVRP_LOG_EVENT'
629#if defined( __ibm )
630    CALL FLUSH_( 9 )
631#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
632    CALL FLUSH( 9 )
633#endif
634
635#if defined( __parallel )
636!
637!-- Find out, if dvrp output shall be done by a dedicated PE
638    CALL local_getenv( 'use_seperate_pe_for_dvrp_output', 31, chr, idummy )
639    IF ( chr == 'true' )  THEN
640       use_seperate_pe_for_dvrp_output = .TRUE.
641    WRITE ( 9, * ) '*** myid=', myid, ' vor DVRP_SPLIT'
642#if defined( __ibm )
643    CALL FLUSH_( 9 )
644#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
645    CALL FLUSH( 9 )
646#endif
647       CALL DVRP_SPLIT( MPI_COMM_WORLD, comm_palm )
648    WRITE ( 9, * ) '*** myid=', myid, ' nach DVRP_SPLIT'
649#if defined( __ibm )
650    CALL FLUSH_( 9 )
651#elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
652    CALL FLUSH( 9 )
653#endif
654       CALL MPI_COMM_SIZE( comm_palm, numprocs, ierr )
655    ENDIF
656#endif
657
658#endif
659 END SUBROUTINE init_dvrp_logging
660
661
662 SUBROUTINE close_dvrp
663
664!------------------------------------------------------------------------------!
665! Description:
666! ------------
667! Exit of dvrp software and finish dvrp logging
668!------------------------------------------------------------------------------!
669#if defined( __dvrp_graphics )
670
671    USE control_parameters
672    USE dvrp
673    USE dvrp_variables
674
675    INTEGER ::  m
676
677!
678!-- If required, close dvrp-software and logging of dvrp-calls
679    IF ( dt_dvrp /= 9999999.9 )  THEN
680       m = 1
681       DO WHILE ( mode_dvrp(m) /= ' ' )
682          CALL DVRP_EXIT( m-1 )
683          m = m + 1
684       ENDDO
685       CALL DVRP_LOG_EVENT( -1, 1 )   ! Logging of total cpu-time used by PALM
686       IF ( use_seperate_pe_for_dvrp_output )  THEN
687          CALL DVRP_SPLIT_EXIT( 1 )      ! Argument 0: reduced output
688       ELSE
689          CALL DVRP_LOG_EXIT( 1 )        ! Argument 0: reduced output
690       ENDIF
691    ENDIF
692
693#endif
694 END SUBROUTINE close_dvrp
Note: See TracBrowser for help on using the repository browser.