source: palm/trunk/UTIL/surface_output_processing/surface_output_to_vtk.f90 @ 4784

Last change on this file since 4784 was 4784, checked in by suehring, 3 years ago

surface data output processing to vtk format: Output of 5 relevant digits rather than 1 for the point data in order to account also for small grid spacings; Give path to surface data directly; Remove non-used input variables

  • Property svn:keywords set to Id
File size: 20.4 KB
Line 
1!> @file surface_output_merge.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2020  Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: surface_output_to_vtk.f90 4784 2020-11-13 18:24:56Z suehring $
27! - Give path to surface data directly
28! - Remove non-used input variables
29! - Output 5 relevant digits for the point data in order to account also for
30!   small grid spacings
31!
32! 4481 2020-03-31 18:55:54Z maronga
33! Add suffix to VTK output to indicate average data
34!
35! 3805 2019-03-20 15:26:35Z raasch
36! output format adjusted
37!
38! 3755 2019-02-19 17:03:19Z suehring
39! - Change format description to avoid *** for larger domains
40! - switch back from to non-standard Fortran ftell and fseek since posix
41!   interface do not work any more for some unknown reason
42!
43! 3523 2018-11-13 16:09:31Z suehring
44! Implement interface for posix conform C-systemcalls in order to replace
45! non-standard FORTRAN functions ftell and fseek.
46!
47! 3496 2018-11-06 15:59:50Z suehring
48! Use subroutine call for fseek instead of function call. gfortran has some
49! problems with this.
50!
51! 3494 2018-11-06 14:51:27Z suehring
52! Initial version
53!
54! Authors:
55! --------
56! @author Matthias Suehring and Klaus Ketelsen
57!
58!------------------------------------------------------------------------------!
59! Description:
60! ------------
61!> Interface to posix systemcalls. The module allows to call the following
62!> C system calls from FORTRAN: ftell, lseek.
63!------------------------------------------------------------------------------!
64 MODULE posix_interface
65 
66    INTERFACE
67       INTEGER (C_SIZE_T) FUNCTION C_LSEEK (fd, offset, whence)                &
68                                   BIND(C, NAME='lseek')
69         
70          USE ISO_C_BINDING
71         
72          IMPLICIT NONE
73         
74          INTEGER(KIND=C_INT),    VALUE ::  fd
75          INTEGER(KIND=C_SIZE_T), VALUE ::  offset
76          INTEGER(KIND=C_INT),    VALUE ::  whence
77         
78       END FUNCTION C_LSEEK
79       
80    END INTERFACE
81   
82    INTERFACE
83       INTEGER (C_SIZE_T) FUNCTION C_FTELL ( fd )                              &
84                                   BIND(C, NAME='ftell')
85         
86          USE ISO_C_BINDING
87         
88          IMPLICIT NONE
89         
90          INTEGER(KIND=C_INT),    VALUE ::  fd
91
92       END FUNCTION C_FTELL
93       
94    END INTERFACE
95   
96    PUBLIC posix_lseek, posix_ftell
97   
98    CONTAINS
99!
100!------------------------------------------------------------------------------!
101! Description:
102! ------------
103!> Interface for the C-routine lseek.
104!------------------------------------------------------------------------------!
105    SUBROUTINE posix_lseek( fid, offset )
106   
107       USE ISO_C_BINDING
108   
109       IMPLICIT NONE
110
111       INTEGER,INTENT(IN)                     ::  fid    !< file unit
112       INTEGER(KIND=C_SIZE_T),INTENT(IN)      ::  offset !< file offset from the beginning
113
114       INTEGER(KIND=C_INT)                    ::  my_fid !< file unit
115       INTEGER(KIND=C_SIZE_T)                 ::  retval !< return value
116       INTEGER(KIND=C_INT)                    ::  whence !< mode, here start from the beginning
117
118       my_fid = fid
119       whence = 0
120
121       retval = C_LSEEK( fid, offset, whence )
122       
123    END SUBROUTINE posix_lseek
124!
125!------------------------------------------------------------------------------!
126! Description:
127! ------------
128!> Interface for the C-routine ftell.
129!------------------------------------------------------------------------------!
130    SUBROUTINE posix_ftell( fid, filepos )
131   
132       USE ISO_C_BINDING
133   
134       IMPLICIT NONE
135
136       INTEGER,INTENT(IN)      ::  fid                     !< file unit
137       INTEGER(KIND=C_SIZE_T), INTENT(INOUT)   ::  filepos !< file position
138
139       filepos = C_FTELL( fid )
140       
141    END SUBROUTINE posix_ftell
142
143 END MODULE posix_interface
144!
145!------------------------------------------------------------------------------!
146! Description:
147! ------------
148!> This routine combines surface output from PALM-subdomains into one file.
149!> Output from every processor element is opened and read and output
150!> from all processor elements are written into one file for each timestep
151!> according to Paraview's VTK standard.
152!> Output is distinguished between instantaneous and time-averaged data.
153!------------------------------------------------------------------------------!
154 PROGRAM surface_output_to_vtk
155 
156    USE, INTRINSIC ::  ISO_C_BINDING
157     
158    USE posix_interface,                                                       &
159        ONLY:  posix_ftell, posix_lseek
160
161    IMPLICIT NONE
162   
163    CHARACTER(LEN=4)   ::  char_time              !< string indicating simulated time
164    CHARACTER(LEN=4)   ::  file_suffix = '.bin'   !< string which contain the suffix indicating surface data
165   
166    CHARACTER(LEN=10)  ::  char_dum               !< dummy string
167   
168    CHARACTER(LEN=30)  ::  myid_char              !< combined string indicating binary file
169   
170
171    CHARACTER(LEN=100) ::  path                   !< path to the binary data
172    CHARACTER(LEN=100) ::  variable_name          !< name of the processed output variable   
173
174    INTEGER(4)   ::  ftell                        !< intrinsic function, get current position in file
175    INTEGER(4)   ::  ndum                         !< return parameter of intrinsic function fseek   
176       
177    INTEGER, PARAMETER ::  iwp = 4                !< integer precision
178    INTEGER, PARAMETER ::  wp  = 8                !< float precision
179    INTEGER, PARAMETER ::  OFFSET_KIND = C_SIZE_T !< unsigned integer for the C-interface
180
181    INTEGER(iwp) ::  f                            !< running index over all binary files
182    INTEGER(iwp) ::  file_id_in = 18              !< file unit for input binaray file   
183    INTEGER(iwp) ::  file_id_out = 20             !< file unit for output VTK file       
184    INTEGER(iwp) ::  file_id_out_header = 19      !< file unit for temporary header file
185    INTEGER(iwp) ::  length                       !< length of string on file
186    INTEGER(iwp) ::  n                            !< running index over all points and polygons
187    INTEGER(iwp) ::  npoints_total                !< total number of points
188    INTEGER(iwp) ::  ns_total                     !< total number of polygons
189    INTEGER(iwp) ::  num_pe                       !< number of processors of the run
190
191!     INTEGER(OFFSET_KIND),DIMENSION(:), ALLOCATABLE ::  filepos !< current fileposition in binary file
192    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  filepos !< current fileposition in binary file
193   
194    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  npoints !< number of points/vertices in a binaray file
195    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns      !< number of surface elements in a binaray file
196   
197    LOGICAL ::  convert_average_data = .FALSE.          !< namelist parameter to decide whether average or instantaneous data should be converted
198
199    LOGICAL, DIMENSION(:), ALLOCATABLE      ::  eof     !< flag indicating that end of binary file is reached
200   
201    REAL(wp)                              ::  simulated_time !< output time   
202   
203    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var            !< actual surface data
204   
205    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  points         !< point / vertex data
206    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  polygons       !< polygon data
207    real(wp) :: dum
208   
209    logical :: flag
210
211!
212!-- Read namelist.
213    CALL surface_output_parin
214!
215!-- Allocate array which contains the file position in each output file,
216!-- in order to skip some reading.
217    ALLOCATE( eof(0:num_pe-1)     )
218    ALLOCATE( filepos(0:num_pe-1) )
219    ALLOCATE( npoints(0:num_pe-1) )
220    ALLOCATE( ns(0:num_pe-1)      )
221!
222!-- Initialize file position.
223    filepos = 0
224!
225!-- Open a temporary file which contains all necessary header information for the
226!-- VTK format.
227    OPEN ( file_id_out_header, FILE = 'HEADER', STATUS = 'REPLACE',            &
228           FORM = 'FORMATTED' )
229!
230!-- READ grid setup, i.e. the number and position of vertices and surface elements
231!-- and merge all this information into one file. Further, create all the required
232!-- header information of the VTK file.
233!-- Note, PARAVIEW expects one VTK file for each variable and each timestep.
234!-- Hence, header information needs to be duplicated multiple times.
235!-- Moreover, Paraview expects consecutive vertex and polygon data, which are
236!-- all distributed over the binaray files. Hence, first read vertex data from
237!-- binary file, write this to the HEADER file, close the binary file and read
238!-- data from the next binary file and so on. This requires several openenings
239!-- and closings of the binary files and temporarily storage of the
240!-- file-positions.
241    DO  f = 0, num_pe - 1
242!
243!--    Create filename of the treated binary file.
244       CALL surface_output_create_file_string
245!
246!--    Open file with surface output for processor f.
247       OPEN ( file_id_in, FILE = TRIM( path ) //                               &
248              TRIM( myid_char ), FORM = 'UNFORMATTED' )
249!
250!--    Read number of vertices / points and surface elements
251       READ ( file_id_in )  npoints(f)
252       READ ( file_id_in )  npoints_total
253       READ ( file_id_in )  ns(f)
254       READ ( file_id_in )  ns_total
255!
256!--    Allocate arrays where all the surfaces and vertices will be stored.
257       ALLOCATE( points(3,1:npoints(f))   )
258!
259!--    Read polygon data and store them in a temporary file.
260       READ ( file_id_in )  points
261!
262!--    Obtain current file position. Will be stored for next file opening.
263!        CALL posix_ftell( file_id_in, filepos(f) )
264       filepos(f) = ftell( file_id_in )
265!
266!--    Write header information. Only one time required.
267       IF ( f == 0 )  THEN
268          WRITE( file_id_out_header,'(A)' ) "# vtk DataFile Version 3.0"
269          WRITE( file_id_out_header,'(A,F8.2,A)' ) "legacy vtk File generated by PALM,  simulation time = xxx sec"
270          WRITE( file_id_out_header,'(A)') "ASCII"
271
272          WRITE( file_id_out_header,'(A)') "DATASET POLYDATA"
273          WRITE( file_id_out_header,'(A,I12,A)') "POINTS ", npoints_total, " float"
274       ENDIF     
275!
276!--    Write the vertex data into header file.
277       DO  n = 1, npoints(f)
278          WRITE( file_id_out_header, '(8F15.4)' )  points(1:3,n)
279       ENDDO
280!
281!--    Deallocate vertex data and close binary file.
282       DEALLOCATE( points )
283       
284       CLOSE ( file_id_in )
285    ENDDO
286!
287!-- Now, treat polygon data.
288    DO  f = 0, num_pe - 1
289!
290!--    Create filename of the treated binary file .   
291       CALL surface_output_create_file_string
292!
293!--    Open file with surface output for processor f.
294       OPEN ( file_id_in, FILE = TRIM( path ) //  TRIM( myid_char ), FORM = 'UNFORMATTED' )
295!
296!--    Move to last postion.
297!        CALL posix_lseek( file_id_in, filepos(f) )
298       CALL FSEEK( file_id_in, filepos(f), 0, ndum )
299!
300!--    Allocate array for polygon data
301       ALLOCATE( polygons(5,1:ns(f)) )
302!
303!--    Read polygon data and store them in a temporary file.
304       READ ( file_id_in )  polygons
305!
306!--    Obtain current file position after reading the local polygon data.
307!--    Will be used for next file opening.
308!        CALL posix_ftell( file_id_in, filepos(f) )
309       filepos(f) = ftell( file_id_in )
310!
311!--    Write further header information. Only one time required.
312       IF ( f == 0 )                                                           &
313          WRITE ( file_id_out_header, '(A,2I10)') "POLYGONS ",                 &
314                                                  ns_total, 5 * ns_total
315!
316!--    Write the polygons into the header file. Note, polygon data is of type
317!--    integer, as it just connects the point-indices which describe the given
318!--    surface element.
319       DO n = 1, ns(f)
320          WRITE ( file_id_out_header, '(5I18)' )  INT( polygons(1:5,n) )
321       ENDDO
322!
323!--    Deallocate array for polygon data and close the file.
324       DEALLOCATE( polygons )
325       
326       CLOSE ( file_id_in )
327       
328    ENDDO
329   
330    f = 0
331    CALL surface_output_create_file_string
332!
333!-- Write further header information. Only once required.
334    WRITE ( file_id_out_header, '(A,I10)') "CELL_DATA ", ns_total
335    WRITE ( file_id_out_header, '(A,I10)') "SCALARS cell_scalars float 1 "
336    WRITE ( file_id_out_header, '(A,I10)') "LOOKUP_TABLE default "
337!
338!-- Header creation has now been completed. File can be closed.   
339    CLOSE( file_id_out_header )
340!
341!-- Now, read all the actual data from the surface output. Please note, Paraview
342!-- VTK format expects 1 file per variable and time step.
343!-- The output file is only created once and includes the variable and the
344!-- simulated time.
345!-- In the binaray files, several variables and timesteps are stored, data for a
346!-- given variable, however, is distributed over all binary files. Hence, read
347!-- variable data for a given timestep from the binary file, write this data into
348!-- the target output file, remember file position in binary file and close it,
349!-- open nex binary file and read the variable, and so on, until all variables
350!-- for all timesteps are processed.
351    eof = .FALSE.
352    DO
353       DO  f = 0, num_pe - 1
354!
355!--       Clean up strings-
356          char_time = ''
357          variable_name = ''
358!
359!--       Create filename of the treated binary file.           
360          CALL surface_output_create_file_string
361!
362!--       Open binary file with surface output for processor f.
363          OPEN ( file_id_in, FILE = TRIM( path ) // TRIM( myid_char ), FORM = 'UNFORMATTED' )
364!
365!--       Move to last postion.
366!           CALL posix_lseek( file_id_in, filepos(f) )
367          CALL FSEEK( file_id_in, filepos(f), 0, ndum )
368!
369!--       Read string length and string indicating the output time step.
370          READ ( file_id_in ) length
371          READ ( file_id_in ) char_time(1:length)
372!
373!--       If string for the output time indicates the end-of-file, set the eof
374!--       flag and skip the read of the loop.
375          IF ( char_time(1:length) == 'END' )  THEN
376             eof(f) = .TRUE. 
377             CLOSE ( file_id_in )
378             CYCLE
379          ENDIF
380!
381!--       Read output time, and variable name.
382          READ ( file_id_in ) simulated_time
383          READ ( file_id_in ) length
384          READ ( file_id_in ) variable_name(1:length)
385!
386!--       For first loop index, open the target output file. First create the
387!--       filename string. Further, copy HEADER file with the given filename
388!--       string. The header information must be given in each VTK file!
389          IF ( f == 0 )  THEN
390             IF ( simulated_time < 10.0_wp )  THEN
391                WRITE( char_dum, '(I1)' )  INT( simulated_time ) 
392             ELSEIF ( simulated_time < 100.0_wp )  THEN
393                WRITE( char_dum, '(I2)' )  INT( simulated_time )
394             ELSEIF ( simulated_time < 1000.0_wp )  THEN
395                WRITE( char_dum, '(I3)' )  INT( simulated_time )
396             ELSEIF ( simulated_time < 10000.0_wp )  THEN
397                WRITE( char_dum, '(I4)' )  INT( simulated_time )   
398             ELSEIF ( simulated_time < 100000.0_wp )  THEN
399                WRITE( char_dum, '(I5)' )  INT( simulated_time )   
400             ELSEIF ( simulated_time < 1000000.0_wp )  THEN
401                WRITE( char_dum, '(I6)' )  INT( simulated_time )
402             ELSEIF ( simulated_time < 10000000.0_wp )  THEN
403                WRITE( char_dum, '(I7)' )  INT( simulated_time )   
404             ELSEIF ( simulated_time < 100000000.0_wp )  THEN
405                WRITE( char_dum, '(I8)' )  INT( simulated_time )   
406             ELSEIF ( simulated_time < 1000000000.0_wp )  THEN
407                WRITE( char_dum, '(I9)' )  INT( simulated_time )
408             ENDIF             
409!
410!--          Copy HEADER file and open VTK file
411             IF ( convert_average_data )  THEN
412                CALL system('cp HEADER ' //                                    &
413                            TRIM( path ) // TRIM( char_dum ) //                & 
414                            '_AV_' // 's_' // TRIM( variable_name ) // '.vtk' )
415                           
416                OPEN ( file_id_out, FILE = TRIM( path ) // TRIM( char_dum ) // & 
417                       '_AV_' // 's_' // TRIM( variable_name ) // '.vtk',      &
418                       FORM='FORMATTED', POSITION = 'APPEND' ) 
419             ELSE
420                CALL system('cp HEADER ' //                                    &
421                            TRIM( path ) // TRIM( char_dum ) //                & 
422                            's_' // TRIM( variable_name ) // '.vtk' )
423                           
424                OPEN ( file_id_out, FILE = TRIM( path ) // TRIM( char_dum ) // & 
425                       's_' // TRIM( variable_name ) // '.vtk',                &
426                       FORM='FORMATTED', POSITION = 'APPEND' ) 
427             ENDIF
428
429          ENDIF
430!
431!--       Allocate and read array for variable data. 
432          ALLOCATE( var(1:ns(f)) )
433       
434          READ( file_id_in ) var
435!
436!--       Write variable data into output VTK file.
437          DO n = 1, ns(f)
438             WRITE( file_id_out, * ) var(n)
439          ENDDO
440!
441!--       Remember file position in binary file and close it.
442!           CALL posix_ftell( file_id_in, filepos(f) )
443          filepos(f) = ftell( file_id_in )
444       
445          CLOSE ( file_id_in )
446!
447!--       Deallocate temporary array for variable data.
448          DEALLOCATE( var )
449       
450       ENDDO
451!
452!--    After data for a variable for one time step is read, close the output
453!--    VTK file and go to next variable or timestep.
454       CLOSE ( file_id_out )
455!
456!--    If all files reached the end-of-file, exit the loop.
457       IF ( ALL( eof ) )  EXIT
458       
459    ENDDO
460!
461!-- Finally, remove HEADER file
462    CALL system( 'rm HEADER' )
463   
464 CONTAINS
465 
466!------------------------------------------------------------------------------!
467! Description:
468! ------------
469!> This subroutine read the namelist file.
470!------------------------------------------------------------------------------!
471    SUBROUTINE surface_output_parin
472       
473       IMPLICIT NONE
474       
475       INTEGER(iwp) ::  file_id_parin = 90
476       
477       NAMELIST /surface_output/  convert_average_data, num_pe, path
478
479!
480!--    Open namelist file.
481       OPEN( file_id_parin, FILE='surface_output_parin',                       &
482             STATUS='OLD', FORM='FORMATTED')
483!
484!--    Read namelist.
485       READ ( file_id_parin, surface_output )
486!
487!--    Close namelist file.
488       CLOSE( file_id_parin )
489       
490    END SUBROUTINE surface_output_parin
491     
492!------------------------------------------------------------------------------!
493! Description:
494! ------------
495!> This subroutine creates the filename string of the treated binary file.
496!------------------------------------------------------------------------------!
497    SUBROUTINE surface_output_create_file_string
498
499       IMPLICIT NONE
500
501       CHARACTER(LEN=3) ::  char_av = ''
502!
503!--    Create substring for averaged data.
504       IF ( convert_average_data )  char_av = '_av'
505!
506!--    Create substring for the processor id and combine all substrings.
507       IF ( f < 10 )  THEN
508          WRITE( char_dum, '(I1)')  f
509          myid_char = TRIM( char_av ) // '_00000' // TRIM( char_dum )
510       ELSEIF ( f < 100     )  THEN
511          WRITE( char_dum, '(I2)')  f
512          myid_char = TRIM( char_av ) // '_0000'  // TRIM( char_dum )
513       ELSEIF ( f < 1000    )  THEN
514          WRITE( char_dum, '(I3)')  f
515          myid_char = TRIM( char_av ) // '_000'   // TRIM( char_dum )
516       ELSEIF ( f < 10000   )  THEN
517          WRITE( char_dum, '(I4)')  f
518          myid_char = TRIM( char_av ) // '_00'    // TRIM( char_dum )
519       ELSEIF ( f < 100000  )  THEN
520          WRITE( char_dum, '(I5)')  f
521          myid_char = TRIM( char_av ) // '_0'     // TRIM( char_dum )
522       ELSEIF ( f < 1000000 )  THEN
523          WRITE( char_dum, '(I6)')  f
524          myid_char = TRIM( char_av ) // '_'      // TRIM( char_dum )
525       ENDIF
526       
527    END SUBROUTINE surface_output_create_file_string
528       
529 END PROGRAM surface_output_to_vtk
530
531
532
Note: See TracBrowser for help on using the repository browser.