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

Last change on this file since 4843 was 4843, checked in by raasch, 3 years ago

local namelist parameter added to switch off the module although the respective module namelist appears in the namelist file, further copyright updates

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