The TELEMAC-MASCARET system  trunk
lib_vtk_io.F
Go to the documentation of this file.
1 ! *****************
2  MODULE lib_vtk_io
3 ! *****************
4 !
5 !***********************************************************************
6 ! STBTEL V6P3 06/2013
7 !***********************************************************************
8 !
9 !brief
10 !
11 !history Y.AUDOUIN
12 !+ 30/06/2013
13 !+ V6P3
14 !+
15 !
16 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
17 !| |<-->|
18 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
19 !
20  IMPLICIT NONE
21  PRIVATE
22 #if !defined DISABLE_VTK
23  ! FUNCTIONS FOR VTK LEGACY
24  PUBLIC:: vtk_ini
25  PUBLIC:: vtk_geo
26  PUBLIC:: vtk_con
27  PUBLIC:: vtk_dat
28  PUBLIC:: vtk_var
29  PUBLIC:: vtk_end
30  ! PORTABLE KIND-PRECISION
31  PUBLIC:: r16p, fr16p
32  PUBLIC:: r8p, fr8p
33  PUBLIC:: r4p, fr4p
34  PUBLIC:: r_p, fr_p
35  PUBLIC:: i8p, fi8p
36  PUBLIC:: i4p, fi4p
37  PUBLIC:: i2p, fi2p
38  PUBLIC:: i1p, fi1p
39  PUBLIC:: i_p, fi_p
40  !-----------------------------------------------
41 
42  !----------------------------------------------
43  ! overloading of VTK_GEO
44  INTERFACE vtk_geo
45  MODULE PROCEDURE vtk_geo_unst_r8, ! REAL(R8P) UNSTRUCTURED_GRID
46  & vtk_geo_unst_r4, ! REAL(R4P) UNSTRUCTURED_GRID
47  & vtk_geo_strp_r8, ! REAL(R8P) STRUCTURED_POINTS
48  & vtk_geo_strp_r4, ! REAL(R4P) STRUCTURED_POINTS
49  & vtk_geo_strg_r8, ! REAL(R8P) STRUCTURED_GRID
50  & vtk_geo_strg_r4, ! REAL(R4P) STRUCTURED_GRID
51  & vtk_geo_rect_r8, ! REAL(R8P) RECTILINEAR_GRID
52  & vtk_geo_rect_r4 ! REAL(R4P) RECTILINEAR_GRID
53  END INTERFACE
54  ! overloading of VTK_VAR
55  INTERFACE vtk_var
56  MODULE PROCEDURE vtk_var_scal_r8, ! REAL(R8P) SCALAR
57  & vtk_var_scal_r4, ! REAL(R4P) SCALAR
58  & vtk_var_scal_i4, ! INTEGER(I4P) SCALAR
59  & vtk_var_vect_r8, ! REAL(R8P) VECTORIAL
60  & vtk_var_vect_r4, ! REAL(R4P) VECTORIAL
61  & vtk_var_vect_i4, ! INTEGER(I4P) VECTORIAL
62  & vtk_var_text_r8, ! REAL(R8P) VECTORIAL (TEXTURE)
63  & vtk_var_text_r4 ! REAL(R4P) VECTORIAL (TEXTURE)
64  END INTERFACE
65  !----------------------------------------------------------------------------------------------------------------------------------
66 
67  !----------------------------------------------------------------------------------------------------------------------------------
68  !!\LIBVTKIO has a small set of internal variables and parameters some of which have public visibility.
69  !!
70  !!The \LIBVTKIO uses a partable kind parameters for real and integer variables. The following are the kind parameters used: these
71  !!parameters are public and their use is strong encouraged.
72  !!
73  !!Real precision definitions:
74  !!
75  INTEGER, PARAMETER:: r16p = selected_real_kind(33,4931) ! 33 DIGITS, RANGE $[\PM 10^{-4931} ,\PM 10^{+4931} -1]$
76  INTEGER, PARAMETER:: r8p = selected_real_kind(15,307) ! 15 DIGITS, RANGE $[\PM 10^{-307}~~ ,\PM 10^{+307}~~ -1]$
77  INTEGER, PARAMETER:: r4p = selected_real_kind(6,37) ! 6~~~DIGITS, RANGE $[\PM 10^{-37}~~~~,\PM 10^{+37}~~~~ -1]$
78  INTEGER, PARAMETER:: r_p = r8p ! DEFAULT REAL PRECISION
79  !!Integer precision definitions:
80  !!
81  INTEGER, PARAMETER:: i8p = selected_int_kind(18) ! RANGE $[-2^{63} ,+2^{63} -1]$
82  INTEGER, PARAMETER:: i4p = selected_int_kind(9) ! RANGE $[-2^{31} ,+2^{31} -1]$
83  INTEGER, PARAMETER:: i2p = selected_int_kind(4) ! RANGE $[-2^{15} ,+2^{15} -1]$
84  INTEGER, PARAMETER:: i1p = selected_int_kind(2) ! RANGE $[-2^{7}~~,+2^{7}~~ -1]$
85  INTEGER, PARAMETER:: i_p = i4p ! DEFAULT INTEGER PRECISION
86  !!
87  !!Besides the kind parameters there are also the format parameters useful for writing in a well-ascii-format numeric variables.
88  !!Also these parameters are public.
89  !!
90  !! Real output formats:
91  !!
92  CHARACTER(10), PARAMETER:: fr16p = '(E41.33E4)' ! R16P OUTPUT FORMAT
93  CHARACTER(10), PARAMETER:: fr8p = '(E23.15E3)' ! R8P OUTPUT FORMAT
94  CHARACTER(9), PARAMETER:: fr4p = '(E14.6E2)' ! R4P OUTPUT FORMAT
95  CHARACTER(10), PARAMETER:: fr_p = '(E23.15E3)' ! R\_P OUTPUT FORMAT
96  !! Integer output formats:
97  !!
98  CHARACTER(5), PARAMETER:: fi8p = '(I21)' ! I8P OUTPUT FORMAT
99  CHARACTER(5), PARAMETER:: fi4p = '(I12)' ! I4P OUTPUT FORMAT
100  CHARACTER(4), PARAMETER:: fi2p = '(I7)' ! I2P OUTPUT FORMAT
101  CHARACTER(4), PARAMETER:: fi1p = '(I5)' ! I1P OUTPUT FORMAT
102  CHARACTER(5), PARAMETER:: fi_p = '(I12)' ! I\_P OUTPUT FORMAT
103  !!
104  !!\LIBVTKIO uses a small set of internal variables that are private (not accessible from the outside). The following are
105  !! private variables:
106  !!
107  INTEGER(I4P), PARAMETER:: maxlen = 500 ! MAX NUMBER OF CHARACTERS OS STATIC STRING
108  CHARACTER(1), PARAMETER:: end_rec = char(10) ! END-CHARACTER FOR BINARY-RECORD FINALIZE
109  INTEGER(I4P), PARAMETER:: f_out_ascii = 0 ! ASCII-OUTPUT-FORMAT PARAMETER IDENTIFIER
110  INTEGER(I4P), PARAMETER:: f_out_binary = 1 ! BINARY-OUTPUT-FORMAT PARAMETER IDENTIFIER
111  INTEGER(I4P):: f_out = f_out_ascii ! CURRENT OUTPUT-FORMAT (INITIALIZED TO ASCII FORMAT)
112  CHARACTER(LEN=MAXLEN):: topology ! MESH TOPOLOGY
113  INTEGER(I4P):: unit_vtk ! INTERNAL LOGICAL UNIT
114  !----------------------------------------------------------------------------------------------------------------------------------
115 
116  !!IN THE FOLLOWING CHAPTERS THERE IS THE API REFERENCE OF ALL FUNCTIONS OF \LIBVTKIO.
117  CONTAINS
118  !!\chapter{Auxiliary functions}
119  !!\minitoc
120  !!\vspace*{8mm}
121  !!
122  !!\LIBVTKIO uses two auxiliary functions that are not connected with the VTK standard. These functions are private and so they
123  !!cannot be called outside the library.
124  FUNCTION getunit() RESULT(FREE_UNIT)
125  !--------------------------------------------------------------------------------------------------------------------------------
126  !!The GetUnit function is used for getting a free logic unit. The users of \LIBVTKIO does not know which is
127  !!the logical unit: \LIBVTKIO handels this information without boring the users. The logical unit used is safe-free: if the
128  !!program calling \LIBVTKIO has others logical units used \LIBVTKIO will never use these units, but will choice one that is free.
129  !--------------------------------------------------------------------------------------------------------------------------------
130 
131  IMPLICIT NONE
132 
133  !--------------------------------------------------------------------------------------------------------------------------------
134  INTEGER(I4P):: FREE_UNIT ! FREE LOGIC UNIT
135  INTEGER(I4P):: N1 ! COUNTER
136  INTEGER(I4P):: IOS ! INQUIRING FLAG
137  LOGICAL(4):: LOPEN ! INQUIRING FLAG
138  !--------------------------------------------------------------------------------------------------------------------------------
139 
140  !--------------------------------------------------------------------------------------------------------------------------------
141  !!The following is the code snippet of GetUnit function: the units 0, 5, 6, 9 and all non-free units are discarded.
142  !!
143  !(\doc)codesnippet
144  free_unit = -1_i4p ! INITIALIZING FREE LOGIC UNIT
145  n1=1_i4p ! INITIALIZING COUNTER
146  DO
147  IF ((n1/=5_i4p).AND.(n1/=6_i4p).AND.(n1/=9_i4p)) THEN
148  INQUIRE (unit=n1,opened=lopen,iostat=ios) ! VERIFY LOGIC UNITS
149  IF (ios==0_i4p) THEN
150  IF (.NOT.lopen) THEN
151  free_unit = n1 ! ASSIGNMENT OF FREE LOGIC
152  RETURN
153  ENDIF
154  ENDIF
155  ENDIF
156  n1=n1+1_i4p ! UPDATING COUNTER
157  ENDDO
158  RETURN
159  !(doc/)codesnippet
160  !!GetUnit function is private and cannot be called outside \LIBVTKIO. If you are interested to use it change its scope to public.
161  !--------------------------------------------------------------------------------------------------------------------------------
162  END FUNCTION getunit
163 
164  FUNCTION upper_case(STRING)
165  !--------------------------------------------------------------------------------------------------------------------------------
166  !!The Upper\_Case function converts the lower case characters of a string to upper case one. \LIBVTKIO uses this function in
167  !!order to achieve case-insensitive: all character variables used within \LIBVTKIO functions are pre-processed by
168  !!Uppper\_Case function before these variables are used. So the users can call \LIBVTKIO functions whitout pay attention of the
169  !!case of the kwywords passed to the functions: calling the function VTK\_INI with the string \code{E_IO = VTK_INI('Ascii',...)}
170  !!or with the string \code{E_IO = VTK_INI('AscII',...)} is equivalent.
171  !--------------------------------------------------------------------------------------------------------------------------------
172 
173  IMPLICIT NONE
174 
175  !--------------------------------------------------------------------------------------------------------------------------------
176  CHARACTER(LEN=*), INTENT(IN):: STRING ! STRING TO BE CONVERTED
177  CHARACTER(LEN=LEN(STRING)):: UPPER_CASE ! CONVERTED STRING
178  INTEGER:: N1 ! CHARACTERS COUNTER
179  !--------------------------------------------------------------------------------------------------------------------------------
180 
181  !--------------------------------------------------------------------------------------------------------------------------------
182  !!The following is the code snippet of Upper\_Case function.
183  !!
184  !(\doc)codesnippet
185  upper_case = string
186  DO n1=1,len(string)
187  SELECT CASE(ichar(string(n1:n1)))
188  CASE(97:122)
189  upper_case(n1:n1)=char(ichar(string(n1:n1))-32) ! UPPER CASE CONVERSION
190  ENDSELECT
191  ENDDO
192  RETURN
193  !(doc/)codesnippet
194  !!Upper\_Case function is private and cannot be called outside \LIBVTKIO. If you are interested to use it change its scope
195  !!to public.
196  !--------------------------------------------------------------------------------------------------------------------------------
197  END FUNCTION upper_case
198 
199  !!\chapter{VTK LEGACY functions}
200  !!\minitoc
201  !!\vspace*{8mm}
202  !!
203  FUNCTION vtk_ini(OUTPUT_FORMAT,FILENAME,TITLE,MESH_TOPOLOGY)
204  & result(e_io)
205  !--------------------------------------------------------------------------------------------------------------------------------
206  !!The VTK\_INI function is used for initializing file. This function must be the first to be called.
207  !--------------------------------------------------------------------------------------------------------------------------------
208 
209  IMPLICIT NONE
210 
211  !--------------------------------------------------------------------------------------------------------------------------------
212  CHARACTER(*), INTENT(IN):: OUTPUT_FORMAT ! OUTPUT FORMAT: ASCII OR BINARY
213  CHARACTER(*), INTENT(IN):: FILENAME ! NAME OF FILE
214  CHARACTER(*), INTENT(IN):: TITLE ! TITLE
215  CHARACTER(*), INTENT(IN):: MESH_TOPOLOGY ! MESH TOPOLOGY
216  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
217  !!The VTK\_INI variables have the following meaning:
218  !!
219  !!\begin{description}
220  !! \item[{\color{RoyalBlue}output\_format}] indicates the \virgo{format} of output file. It can assume the following values:
221  !! \begin{enumerateABlu}
222  !! \item \emph{ascii} (it is case insensitive) $\rightarrow$ creating an ascii output file.
223  !! \item \emph{binary} (it is case insensitive) $\rightarrow$ creating a binary (big\_endian encoding) output file.
224  !! \end{enumerateABlu}
225  !! \item[{\color{RoyalBlue}filename}] contains the name (with its path) of the output file.
226  !! \item[{\color{RoyalBlue}title}] contains the title of the VTK dataset.
227  !! \item[{\color{RoyalBlue}topology}] indicates the topology of the mesh and can assume the following values:
228  !! \begin{enumerateABlu}
229  !! \item \emph{STRUCTURED\_POINTS}.
230  !! \item \emph{STRUCTURED\_GRID}.
231  !! \item \emph{UNSTRUCTURED\_GRID}.
232  !! \item \emph{RECTILINEAR\_GRID}.
233  !! \end{enumerateABlu}
234  !! \item[{\color{RoyalBlue}E\_IO}] contains the inquiring integer flag for error handling.
235  !!\end{description}
236  !!
237  !!The following is an example of VTK\_INI calling:
238  !!
239  !!\begin{boxred}{VTK\_INI Calling}
240  !!\begin{verbatim}
241  !!...
242  !!E_IO = VTK_INI('Binary','example.vtk','VTK legacy file','UNSTRUCTURED_GRID')
243  !!...
244  !!\end{verbatim}
245  !!\end{boxred}
246  !!\noindent Note that the \virgo{.vtk} extension is necessary in the file name.
247  !--------------------------------------------------------------------------------------------------------------------------------
248 
249  !--------------------------------------------------------------------------------------------------------------------------------
250  topology = trim(mesh_topology)
251  unit_vtk=getunit()
252  SELECT CASE(trim(upper_case(output_format)))
253  CASE('ASCII')
255  OPEN(unit = unit_vtk,
256  & file = trim(filename),
257  & form = 'FORMATTED',
258  & access = 'SEQUENTIAL',
259  & action = 'WRITE',
260 ! & BUFFERED = 'YES',
261  & iostat = e_io)
262  ! WRITING HEADER OF FILE
263  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
264  & '# vtk DataFile Version 3.0'
265  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)trim(title)
266  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
267  & trim(upper_case(output_format))
268  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
269  & 'DATASET '//trim(topology)
270  CASE('BINARY')
272  OPEN(unit = unit_vtk,
273  & file = trim(filename),
274  & form = 'UNFORMATTED',
275  & access = 'SEQUENTIAL',
276  & action = 'WRITE',
277 ! & RECORDTYPE = 'STREAM',
278 ! & BUFFERED = 'YES',
279  & iostat = e_io)
280  ! WRITING HEADER OF FILE
281  WRITE(unit=unit_vtk,iostat=e_io)'# vtk DataFile Version 3.0'//
282  & end_rec
283  WRITE(unit=unit_vtk,iostat=e_io)trim(title)//end_rec
284  WRITE(unit=unit_vtk,iostat=e_io)
285  & trim(upper_case(output_format))//end_rec
286  WRITE(unit=unit_vtk,iostat=e_io)'DATASET '//trim(topology)//
287  & end_rec
288  ENDSELECT
289  RETURN
290  !--------------------------------------------------------------------------------------------------------------------------------
291  END FUNCTION vtk_ini
292 
293  !!\section{VTK\_GEO}
294  !!
295  !!VTK\_GEO is an interface to 8 different functions; there are 2 functions for each 4 different topologies actually supported:
296  !!one function for mesh coordinates with R8P precision and one for mesh coordinates with R4P precision.
297  !!This function must be called after VTK\_INI. It saves the mesh geometry. The inputs that must be passed change depending on
298  !!the topologies choiced. Not all VTK topologies have been implemented (\virgo{polydata} topologies are absent). The signatures
299  !!for all implemented topologies are now reported.
300  !!
301  !!\subsection{VTK\_GEO STRUCTURED POINTS}
302  !!
303  !!\begin{boxred}{}
304  !!\begin{lstlisting}[style=signature,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Structured Points Signature}]
305  !! function VTK_GEO(NX,NY,NZ,X0,Y0,Z0,Dx,Dy,Dz) result(E_IO)
306  !!\end{lstlisting}
307  !!\end{boxred}
308  !!
309  !!The topology \virgo{structured points} is useful for structured grid with uniform discretization steps.
310  !!
311  !!\begin{boxred}{}
312  !!\begin{lstlisting}[style=variables,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Structured Points Variables}]
313  !!integer(I4P), intent(IN):: NX ! number of nodes in x direction
314  !!integer(I4P), intent(IN):: NY ! number of nodes in y direction
315  !!integer(I4P), intent(IN):: NZ ! number of nodes in z direction
316  !!real(R8P or R4P), intent(IN):: X0 ! x coordinate of origin
317  !!real(R8P or R4P), intent(IN):: Y0 ! y coordinate of origin
318  !!real(R8P or R4P), intent(IN):: Z0 ! z coordinate of origin
319  !!real(R8P or R4P), intent(IN):: Dx ! space step in x
320  !!real(R8P or R4P), intent(IN):: Dy ! space step in y
321  !!real(R8P or R4P), intent(IN):: Dz ! space step in z
322  !!integer(I4P):: E_IO ! Input/Output inquiring flag: $0$ if IO is done, $> 0$ if IO is not done
323  !!\end{lstlisting}
324  !!\end{boxred}
325  !!
326  !!Note that the variables \texttt{X0,Y0,Z0,Dx,Dy,Dz} can be passed both as 8-byte real kind and 4-byte real kind; the dynamic
327  !!displacement interface will call the correct function. Mixing 8-byte real kind and 4-byte real kind is not allowed: be sure
328  !!that all variables are 8-byte real kind or all are 4-byte real kind.
329  !!
330  !!The VTK\_GEO structured point variables have the following meaning:
331  !!
332  !!\begin{description}
333  !! \item[{\color{RoyalBlue}NX}] indicates the number of nodes in $X$ direction.
334  !! \item[{\color{RoyalBlue}NY}] indicates the number of nodes in $Y$ direction.
335  !! \item[{\color{RoyalBlue}NZ}] indicates the number of nodes in $Z$ direction.
336  !! \item[{\color{RoyalBlue}X0}] indicates the $X$ value of coordinates system origin. It is a scalar.
337  !! \item[{\color{RoyalBlue}Y0}] indicates the $Y$ value of coordinates system origin. It is a scalar.
338  !! \item[{\color{RoyalBlue}Z0}] indicates the $Z$ value of coordinates system origin. It is a scalar.
339  !! \item[{\color{RoyalBlue}Dx}] indicates the uniform grid step discretization in $X$ direction. It is a scalar.
340  !! \item[{\color{RoyalBlue}Dy}] indicates the uniform grid step discretization in $Y$ direction. It is a scalar.
341  !! \item[{\color{RoyalBlue}DZ}] indicates the uniform grid step discretization in $Z$ direction. It is a scalar.
342  !! \item[{\color{RoyalBlue}E\_IO}] contains the inquiring integer flag for error handling.
343  !!\end{description}
344  !!
345  !!The following is an example of VTK\_GEO structured point calling:
346  !!
347  !!\begin{boxred}{VTK\_GEO Structured Points Calling}
348  !!\begin{verbatim}
349  !!...
350  !!integer(4):: NX,NY,NZ
351  !!real(8):: X0,Y0,Z0
352  !!real(8):: Dx,Dy,Dz
353  !!...
354  !!E_IO = VTK_GEO(NX,NY,NZ, &
355  !! X0,Y0,Z0,Dx,Dy,Dz)
356  !!...
357  !!\end{verbatim}
358  !!\end{boxred}
359  !!
360  !!\subsection{VTK\_GEO STRUCTURED GRID}
361  !!
362  !!\begin{boxred}{}
363  !!\begin{lstlisting}[style=signature,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Structured Grid Signature}]
364  !!function VTK_GEO(NX,NY,NZ,NN,X,Y,Z) result(E_IO)
365  !!\end{lstlisting}
366  !!\end{boxred}
367  !!
368  !!The topology \virgo{structured grid} is useful for structured grid with non-uniform discretization steps.
369  !!
370  !!\begin{boxred}{}
371  !!\begin{lstlisting}[style=variables,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Structured Grid Variables}]
372  !!integer(I4P), intent(IN):: NX ! number of nodes in x direction
373  !!integer(I4P), intent(IN):: NY ! number of nodes in y direction
374  !!integer(I4P), intent(IN):: NZ ! number of nodes in z direction
375  !!integer(I4P), intent(IN):: NN ! number of all nodes
376  !!real(R8P or R4P), intent(IN):: X(1:NN) ! x coordinates
377  !!real(R8P or R4P), intent(IN):: Y(1:NN) ! y coordinates
378  !!real(R8P or R4P), intent(IN):: Z(1:NN) ! z coordinates
379  !!integer(I4P):: E_IO ! Input/Output inquiring flag: $0$ if IO is done, $> 0$ if IO is not done
380  !!\end{lstlisting}
381  !!\end{boxred}
382  !!
383  !!Note that the variables \texttt{X,Y,Z} can be passed both as 8-byte real kind and 4-byte real kind; the dynamic
384  !!displacement interface will call the correct function. Mixing 8-byte real kind and 4-byte real kind is not allowed: be
385  !!sure that all variables are 8-byte real kind or all are 4-byte real kind.
386  !!
387  !!The VTK\_GEO structured grid variables have the following meaning:
388  !!
389  !!\begin{description}
390  !! \item[{\color{RoyalBlue}NX}] indicates the number of nodes in $X$ direction.
391  !! \item[{\color{RoyalBlue}NY}] indicates the number of nodes in $Y$ direction.
392  !! \item[{\color{RoyalBlue}NZ}] indicates the number of nodes in $Z$ direction.
393  !! \item[{\color{RoyalBlue}NN}] indicates the number of all nodes, $NN= NX\cdot NY\cdot NZ$.
394  !! \item[{\color{RoyalBlue}X}] contains the $X$ coordinates values of all nodes. It is a vector of $[1:NN]$.
395  !! \item[{\color{RoyalBlue}Y}] contains the $Y$ coordinates values of all nodes. It is a vector of $[1:NN]$.
396  !! \item[{\color{RoyalBlue}Z}] contains the $Z$ coordinates values of all nodes. It is a vector of $[1:NN]$.
397  !! \item[{\color{RoyalBlue}E\_IO}] contains the inquiring integer flag for error handling.
398  !!\end{description}
399  !!
400  !!The following is an example of VTK\_GEO structured grid calling:
401  !!
402  !!\begin{boxred}{VTK\_GEO Structured Grid Calling}
403  !!\begin{verbatim}
404  !!...
405  !!integer(4), parameter:: NX=10,NY=10,NZ=10
406  !!integer(4), parameter:: Nnodi=NX*NY*NZ
407  !!real(8):: X(1:Nnodi),Y(1:Nnodi),Z(1:Nnodi)
408  !!...
409  !!E_IO = VTK_GEO(NX,NY,NZ,Nnodi,X,Y,Z)
410  !!...
411  !!\end{verbatim}
412  !!\end{boxred}
413  !!
414  !!\subsection{VTK\_GEO RECTILINEAR GRID}
415  !!
416  !!\begin{boxred}{}
417  !!\begin{lstlisting}[style=signature,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Rectilinear Grid Signature}]
418  !!function VTK_GEO(NX,NY,NZ,X,Y,Z) result(E_IO)
419  !!\end{lstlisting}
420  !!\end{boxred}
421  !!
422  !!The topology \virgo{rectilinear grid} is useful for structured grid with non-uniform discretization steps even
423  !!in generalized coordinates.
424  !!
425  !!\begin{boxred}{}
426  !!\begin{lstlisting}[style=variables,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Rectilinear Grid Signature}]
427  !!integer(I4P), intent(IN):: NX ! number of nodes in x direction
428  !!integer(I4P), intent(IN):: NY ! number of nodes in y direction
429  !!integer(I4P), intent(IN):: NZ ! number of nodes in z direction
430  !!real(R8P or R4P), intent(IN):: X(1:NX) ! x coordinates
431  !!real(R8P or R4P), intent(IN):: Y(1:NY) ! y coordinates
432  !!real(R8P or R4P), intent(IN):: Z(1:NZ) ! z coordinates
433  !!integer(I4P):: E_IO ! Input/Output inquiring flag: $0$ if IO is done, $> 0$ if IO is not done
434  !!\end{lstlisting}
435  !!\end{boxred}
436  !!
437  !!Note that the variables \texttt{X,Y,Z} can be passed both as 8-byte real kind and 4-byte real kind; the dynamic
438  !!displacement interface will call the correct function. Mixing 8-byte real kind and 4-byte real kind is not allowed: be
439  !!sure that all variables are 8-byte real kind or all are 4-byte real kind.
440  !!
441  !!The VTK\_GEO rectilinear grid variables have the following meaning:
442  !!
443  !!\begin{description}
444  !! \item[{\color{RoyalBlue}NX}] indicates the number of nodes in $X$ direction.
445  !! \item[{\color{RoyalBlue}NY}] indicates the number of nodes in $Y$ direction.
446  !! \item[{\color{RoyalBlue}NZ}] indicates the number of nodes in $Z$ direction.
447  !! \item[{\color{RoyalBlue}X}] contains the $X$ coordinates values of nodes. It is a vector of $[1:NX]$.
448  !! \item[{\color{RoyalBlue}Y}] contains the $Y$ coordinates values of nodes. It is a vector of $[1:NY]$.
449  !! \item[{\color{RoyalBlue}Z}] contains the $Z$ coordinates values of nodes. It is a vector of $[1:NZ]$.
450  !! \item[{\color{RoyalBlue}E\_IO}] contains the inquiring integer flag for error handling.
451  !!\end{description}
452  !!
453  !!The following is an example of VTK\_GEO rectilinear grid calling:
454  !!
455  !!\begin{boxred}{VTK\_GEO Rectilinear Grid Calling}
456  !!\begin{verbatim}
457  !!...
458  !!integer(4), parameter:: NX=10,NY=20,NZ=30
459  !!real(4):: X(1:NX),Y(1:NY),Z(1:NZ)
460  !!...
461  !!E_IO = VTK_GEO(NX,NY,NZ,X,Y,Z)
462  !!...
463  !!\end{verbatim}
464  !!\end{boxred}
465  !!
466  !!\subsection{VTK\_GEO UNSTRUCTURED GRID}
467  !!
468  !!\begin{boxred}{}
469  !!\begin{lstlisting}[style=signature,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Unstructured Grid Signature}]
470  !!function VTK_GEO(Nnodi,X,Y,Z) result(E_IO)
471  !!\end{lstlisting}
472  !!\end{boxred}
473  !!
474  !!The topology \virgo{unstructured grid} is necessary for unstructured grid, the most general mesh format. This
475  !!topology is also useful for scructured mesh in order to save only a non-structured clip of mesh.
476  !!
477  !!\begin{boxred}{}
478  !!\begin{lstlisting}[style=variables,title=\color{Maroon}\MaiuscolettoBS{VTK\_GEO Unstructured Grid Variables}]
479  !!integer(I4P), intent(IN):: NN ! number of nodes
480  !!real(R8P or R4P), intent(IN):: X(1:NN) ! x coordinates of all nodes
481  !!real(R8P or R4P), intent(IN):: Y(1:NN) ! y coordinates of all nodes
482  !!real(R8P or R4P), intent(IN):: Z(1:NN) ! z coordinates of all nodes
483  !!integer(I4P):: E_IO ! Input/Output inquiring flag: $0$ if IO is done, $> 0$ if IO is not done
484  !!\end{lstlisting}
485  !!\end{boxred}
486  !!
487  !!Note that the variables \texttt{X,Y,Z} can be passed both as 8-byte real kind and 4-byte real kind; the dynamic
488  !!displacement interface will call the correct function. Mixing 8-byte real kind and 4-byte real kind is not allowed: be
489  !!sure that all variables are 8-byte real kind or all are 4-byte real kind.
490  !!
491  !!The VTK\_GEO unstructured grid variables have the following meaning:
492  !!
493  !!\begin{description}
494  !! \item[{\color{RoyalBlue}NN}] indicates the number of all nodes.
495  !! \item[{\color{RoyalBlue}X}] contains the $X$ coordinates values of nodes. It is a vector of $[1:NN]$.
496  !! \item[{\color{RoyalBlue}Y}] contains the $Y$ coordinates values of nodes. It is a vector of $[1:NN]$.
497  !! \item[{\color{RoyalBlue}Z}] contains the $Z$ coordinates values of nodes. It is a vector of $[1:NN]$.
498  !! \item[{\color{RoyalBlue}E\_IO}] contains the inquiring integer flag for error handling.
499  !!\end{description}
500  !!
501  !!The following is an example of VTK\_GEO unstructured grid calling:
502  !!
503  !!\begin{boxred}{VTK\_GEO Unstructured Grid Calling}
504  !!\begin{verbatim}
505  !!...
506  !!integer(4), parameter:: NN=100
507  !!real(4):: X(1:NN),Y(1:NN),Z(1:NN)
508  !!...
509  !!E_IO = VTK_GEO(NN,X,Y,Z)
510  !!...
511  !!\end{verbatim}
512  !!\end{boxred}
513  !!
514  !!In order to use the \virgo{unstructured grid} it is necessary to save also the \virgo{connectivity} of the grid. The
515  !!connectivity must be saved with the function \MaiuscolettoBS{VTK\_CON}.
516  !!
517  !(\doc)skippedblock
518  FUNCTION vtk_geo_strp_r8(NX,NY,NZ,X0,Y0,Z0,DX,DY,DZ)
519  & result(e_io)
520  !--------------------------------------------------------------------------------------------------------------------------------
521  !! FUNCTION FOR SAVING MESH; TOPOLOGY = STRUCTURED\_POINTS (R8P).
522  !--------------------------------------------------------------------------------------------------------------------------------
523 
524  IMPLICIT NONE
525 
526  !--------------------------------------------------------------------------------------------------------------------------------
527  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
528  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
529  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
530  REAL(R8P), INTENT(IN):: X0 ! X COORDINATE OF ORIGIN
531  REAL(R8P), INTENT(IN):: Y0 ! Y COORDINATE OF ORIGIN
532  REAL(R8P), INTENT(IN):: Z0 ! Z COORDINATE OF ORIGIN
533  REAL(R8P), INTENT(IN):: DX ! SPACE STEP IN X DIRECTION
534  REAL(R8P), INTENT(IN):: DY ! SPACE STEP IN Y DIRECTION
535  REAL(R8P), INTENT(IN):: DZ ! SPACE STEP IN Z DIRECTION
536  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
537  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
538  !--------------------------------------------------------------------------------------------------------------------------------
539 
540  !--------------------------------------------------------------------------------------------------------------------------------
541  SELECT CASE(f_out)
542  CASE(f_out_ascii)
543  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
544  & 'DIMENSIONS ',nx,ny,nz
545  WRITE(unit=unit_vtk,fmt='(A,3'//fr8p//')', iostat=e_io)
546  & 'ORIGIN ',x0,y0,z0
547  WRITE(unit=unit_vtk,fmt='(A,3'//fr8p//')', iostat=e_io)
548  & 'SPACING ',dx,dy,dz
549  CASE(f_out_binary)
550  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
551  & 'DIMENSIONS ',nx,ny,nz
552  WRITE(unit=unit_vtk, iostat=e_io)
553  & trim(s_buffer)//end_rec
554  WRITE(s_buffer, fmt='(A,3'//fr8p//')', iostat=e_io)
555  & 'ORIGIN ',x0,y0,z0
556  WRITE(unit=unit_vtk, iostat=e_io)
557  & trim(s_buffer)//end_rec
558  WRITE(s_buffer, fmt='(A,3'//fr8p//')', iostat=e_io)
559  & 'SPACING ',dx,dy,dz
560  WRITE(unit=unit_vtk, iostat=e_io)
561  & trim(s_buffer)//end_rec
562  ENDSELECT
563  RETURN
564  !--------------------------------------------------------------------------------------------------------------------------------
565  END FUNCTION vtk_geo_strp_r8
566 
567  FUNCTION vtk_geo_strp_r4(NX,NY,NZ,X0,Y0,Z0,DX,DY,DZ)
568  & result(e_io)
569  !--------------------------------------------------------------------------------------------------------------------------------
570  !! FUNCTION FOR SAVING MESH; TOPOLOGY = STRUCTURED\_POINTS (R4P).
571  !--------------------------------------------------------------------------------------------------------------------------------
572 
573  IMPLICIT NONE
574 
575  !--------------------------------------------------------------------------------------------------------------------------------
576  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
577  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
578  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
579  REAL(R4P), INTENT(IN):: X0 ! X COORDINATE OF ORIGIN
580  REAL(R4P), INTENT(IN):: Y0 ! Y COORDINATE OF ORIGIN
581  REAL(R4P), INTENT(IN):: Z0 ! Z COORDINATE OF ORIGIN
582  REAL(R4P), INTENT(IN):: DX ! SPACE STEP IN X DIRECTION
583  REAL(R4P), INTENT(IN):: DY ! SPACE STEP IN Y DIRECTION
584  REAL(R4P), INTENT(IN):: DZ ! SPACE STEP IN Z DIRECTION
585  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
586  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
587  !--------------------------------------------------------------------------------------------------------------------------------
588 
589  !--------------------------------------------------------------------------------------------------------------------------------
590  SELECT CASE(f_out)
591  CASE(f_out_ascii)
592  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
593  & 'DIMENSIONS ',nx,ny,nz
594  WRITE(unit=unit_vtk,fmt='(A,3'//fr4p//')', iostat=e_io)
595  & 'ORIGIN ',x0,y0,z0
596  WRITE(unit=unit_vtk,fmt='(A,3'//fr4p//')', iostat=e_io)
597  & 'SPACING ',dx,dy,dz
598  CASE(f_out_binary)
599  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
600  & 'DIMENSIONS ',nx,ny,nz
601  WRITE(unit=unit_vtk, iostat=e_io)
602  & trim(s_buffer)//end_rec
603  WRITE(s_buffer, fmt='(A,3'//fr4p//')', iostat=e_io)
604  & 'ORIGIN ',x0,y0,z0
605  WRITE(unit=unit_vtk, iostat=e_io)
606  & trim(s_buffer)//end_rec
607  WRITE(s_buffer, fmt='(A,3'//fr4p//')', iostat=e_io)
608  & 'SPACING ',dx,dy,dz
609  WRITE(unit=unit_vtk, iostat=e_io)
610  & trim(s_buffer)//end_rec
611  ENDSELECT
612  RETURN
613  !--------------------------------------------------------------------------------------------------------------------------------
614  END FUNCTION vtk_geo_strp_r4
615 
616  FUNCTION vtk_geo_strg_r8(NX,NY,NZ,NN,X,Y,Z) RESULT(E_IO)
617  !--------------------------------------------------------------------------------------------------------------------------------
618  !! FUNCTION FOR SAVING MESH; TOPOLOGY = STRUCTURED\_GRID (R8P).
619  !--------------------------------------------------------------------------------------------------------------------------------
620 
621  IMPLICIT NONE
622 
623  !--------------------------------------------------------------------------------------------------------------------------------
624  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
625  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
626  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
627  INTEGER(I4P), INTENT(IN):: NN ! NUMBER OF ALL NODES
628  REAL(R8P), INTENT(IN):: X(1:nn) ! X COORDINATES
629  REAL(R8P), INTENT(IN):: Y(1:nn) ! Y COORDINATES
630  REAL(R8P), INTENT(IN):: Z(1:nn) ! Z COORDINATES
631  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
632  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
633  INTEGER(I4P):: N1 ! COUNTER
634  !--------------------------------------------------------------------------------------------------------------------------------
635 
636  !--------------------------------------------------------------------------------------------------------------------------------
637  SELECT CASE(f_out)
638  CASE(f_out_ascii)
639  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
640  & 'DIMENSIONS ',nx,ny,nz
641  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
642  & 'POINTS ',nn,' double'
643  WRITE(unit=unit_vtk,fmt='(3'//fr8p//')', iostat=e_io)
644  & (x(n1),y(n1),z(n1),n1=1,nn)
645  CASE(f_out_binary)
646  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
647  & 'DIMENSIONS ',nx,ny,nz
648  WRITE(unit=unit_vtk, iostat=e_io)
649  & trim(s_buffer)//end_rec
650  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
651  & 'POINTS ',nn,' double'
652  WRITE(unit=unit_vtk, iostat=e_io)
653  & trim(s_buffer)//end_rec
654  WRITE(unit=unit_vtk, iostat=e_io)
655  & (x(n1),y(n1),z(n1),n1=1,nn)
656  WRITE(unit=unit_vtk, iostat=e_io)end_rec
657  ENDSELECT
658  RETURN
659  !--------------------------------------------------------------------------------------------------------------------------------
660  END FUNCTION vtk_geo_strg_r8
661 
662  FUNCTION vtk_geo_strg_r4(NX,NY,NZ,NN,X,Y,Z) RESULT(E_IO)
663  !--------------------------------------------------------------------------------------------------------------------------------
664  !! FUNCTION FOR SAVING MESH; TOPOLOGY = STRUCTURED\_GRID (R4P).
665  !--------------------------------------------------------------------------------------------------------------------------------
666 
667  IMPLICIT NONE
668 
669  !--------------------------------------------------------------------------------------------------------------------------------
670  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
671  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
672  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
673  INTEGER(I4P), INTENT(IN):: NN ! NUMBER OF ALL NODES
674  REAL(R4P), INTENT(IN):: X(1:nn) ! X COORDINATES
675  REAL(R4P), INTENT(IN):: Y(1:nn) ! Y COORDINATES
676  REAL(R4P), INTENT(IN):: Z(1:nn) ! Z COORDINATES
677  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
678  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
679  INTEGER(I4P):: N1 ! COUNTER
680  !--------------------------------------------------------------------------------------------------------------------------------
681 
682  !--------------------------------------------------------------------------------------------------------------------------------
683  SELECT CASE(f_out)
684  CASE(f_out_ascii)
685  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
686  & 'DIMENSIONS ',nx,ny,nz
687  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
688  & 'POINTS ',nn,' float'
689  WRITE(unit=unit_vtk,fmt='(3'//fr4p//')', iostat=e_io)
690  & (x(n1),y(n1),z(n1),n1=1,nn)
691  CASE(f_out_binary)
692  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
693  & 'DIMENSIONS ',nx,ny,nz
694  WRITE(unit=unit_vtk, iostat=e_io)
695  & trim(s_buffer)//end_rec
696  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
697  & 'POINTS ',nn,' float'
698  WRITE(unit=unit_vtk, iostat=e_io)
699  & trim(s_buffer)//end_rec
700  WRITE(unit=unit_vtk, iostat=e_io)
701  & (x(n1),y(n1),z(n1),n1=1,nn)
702  WRITE(unit=unit_vtk, iostat=e_io)end_rec
703  ENDSELECT
704  RETURN
705  !--------------------------------------------------------------------------------------------------------------------------------
706  END FUNCTION vtk_geo_strg_r4
707 
708  FUNCTION vtk_geo_rect_r8(NX,NY,NZ,X,Y,Z) RESULT(E_IO)
709  !--------------------------------------------------------------------------------------------------------------------------------
710  !! FUNCTION FOR SAVING MESH; TOPOLOGY = RECTILINEAR\_GRID (R8P).
711  !--------------------------------------------------------------------------------------------------------------------------------
712 
713  IMPLICIT NONE
714 
715  !--------------------------------------------------------------------------------------------------------------------------------
716  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
717  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
718  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
719  REAL(R8P), INTENT(IN):: X(1:nx) ! X COORDINATES
720  REAL(R8P), INTENT(IN):: Y(1:ny) ! Y COORDINATES
721  REAL(R8P), INTENT(IN):: Z(1:nz) ! Z COORDINATES
722  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
723  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
724  INTEGER(I4P):: N1 ! COUNTER
725  !--------------------------------------------------------------------------------------------------------------------------------
726 
727  !--------------------------------------------------------------------------------------------------------------------------------
728  SELECT CASE(f_out)
729  CASE(f_out_ascii)
730  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
731  & 'DIMENSIONS ',nx,ny,nz
732  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
733  & 'X_COORDINATES ',nx,' double'
734  WRITE(unit=unit_vtk,fmt=fr8p, iostat=e_io)
735  & (x(n1),n1=1,nx)
736  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
737  & 'Y_COORDINATES ',ny,' double'
738  WRITE(unit=unit_vtk,fmt=fr8p, iostat=e_io)
739  & (y(n1),n1=1,ny)
740  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
741  & 'Z_COORDINATES ',nz,' double'
742  WRITE(unit=unit_vtk,fmt=fr8p, iostat=e_io)
743  & (z(n1),n1=1,nz)
744  CASE(f_out_binary)
745  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
746  & 'DIMENSIONS ',nx,ny,nz
747  WRITE(unit=unit_vtk, iostat=e_io)
748  & trim(s_buffer)//end_rec
749  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
750  & 'X_COORDINATES ',nx,' double'
751  WRITE(unit=unit_vtk, iostat=e_io)
752  & trim(s_buffer)//end_rec
753  WRITE(unit=unit_vtk, iostat=e_io)
754  & (x(n1),n1=1,nx)
755  WRITE(unit=unit_vtk, iostat=e_io)end_rec
756  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
757  & 'Y_COORDINATES ',ny,' double'
758  WRITE(unit=unit_vtk, iostat=e_io)
759  & trim(s_buffer)//end_rec
760  WRITE(unit=unit_vtk, iostat=e_io)
761  & (y(n1),n1=1,ny)
762  WRITE(unit=unit_vtk, iostat=e_io)end_rec
763  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
764  & 'Z_COORDINATES ',nz,' double'
765  WRITE(unit=unit_vtk, iostat=e_io)
766  & trim(s_buffer)//end_rec
767  WRITE(unit=unit_vtk, iostat=e_io)
768  & (z(n1),n1=1,nz)
769  WRITE(unit=unit_vtk, iostat=e_io)end_rec
770  ENDSELECT
771  RETURN
772  !--------------------------------------------------------------------------------------------------------------------------------
773  END FUNCTION vtk_geo_rect_r8
774 
775  FUNCTION vtk_geo_rect_r4(NX,NY,NZ,X,Y,Z) RESULT(E_IO)
776  !--------------------------------------------------------------------------------------------------------------------------------
777  !! FUNCTION FOR SAVING MESH; TOPOLOGY = RECTILINEAR\_GRID (R4P).
778  !--------------------------------------------------------------------------------------------------------------------------------
779 
780  IMPLICIT NONE
781 
782  !--------------------------------------------------------------------------------------------------------------------------------
783  INTEGER(I4P), INTENT(IN):: NX ! NUMBER OF NODES IN X DIRECTION
784  INTEGER(I4P), INTENT(IN):: NY ! NUMBER OF NODES IN Y DIRECTION
785  INTEGER(I4P), INTENT(IN):: NZ ! NUMBER OF NODES IN Z DIRECTION
786  REAL(R4P), INTENT(IN):: X(1:nx) ! X COORDINATES
787  REAL(R4P), INTENT(IN):: Y(1:ny) ! Y COORDINATES
788  REAL(R4P), INTENT(IN):: Z(1:nz) ! Z COORDINATES
789  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
790  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
791  INTEGER(I4P):: N1 ! COUNTER
792  !--------------------------------------------------------------------------------------------------------------------------------
793 
794  !--------------------------------------------------------------------------------------------------------------------------------
795  SELECT CASE(f_out)
796  CASE(f_out_ascii)
797  WRITE(unit=unit_vtk,fmt='(A,3'//fi4p//')', iostat=e_io)
798  & 'DIMENSIONS ',nx,ny,nz
799  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
800  & 'X_COORDINATES ',nx,' float'
801  WRITE(unit=unit_vtk,fmt=fr4p, iostat=e_io)
802  & (x(n1),n1=1,nx)
803  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
804  & 'Y_COORDINATES ',ny,' float'
805  WRITE(unit=unit_vtk,fmt=fr4p, iostat=e_io)
806  & (y(n1),n1=1,ny)
807  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
808  & 'Z_COORDINATES ',nz,' float'
809  WRITE(unit=unit_vtk,fmt=fr4p, iostat=e_io)
810  & (z(n1),n1=1,nz)
811  CASE(f_out_binary)
812  WRITE(s_buffer, fmt='(A,3'//fi4p//')', iostat=e_io)
813  & 'DIMENSIONS ',nx,ny,nz
814  WRITE(unit=unit_vtk, iostat=e_io)
815  & trim(s_buffer)//end_rec
816  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
817  & 'X_COORDINATES ',nx,' float'
818  WRITE(unit=unit_vtk, iostat=e_io)
819  & trim(s_buffer)//end_rec
820  WRITE(unit=unit_vtk, iostat=e_io)
821  & (x(n1),n1=1,nx)
822  WRITE(unit=unit_vtk, iostat=e_io)end_rec
823  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
824  & 'Y_COORDINATES ',ny,' float'
825  WRITE(unit=unit_vtk, iostat=e_io)
826  & trim(s_buffer)//end_rec
827  WRITE(unit=unit_vtk, iostat=e_io)
828  & (y(n1),n1=1,ny)
829  WRITE(unit=unit_vtk, iostat=e_io)end_rec
830  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
831  & 'Z_COORDINATES ',nz,' float'
832  WRITE(unit=unit_vtk, iostat=e_io)
833  & trim(s_buffer)//end_rec
834  WRITE(unit=unit_vtk, iostat=e_io)
835  & (z(n1),n1=1,nz)
836  WRITE(unit=unit_vtk, iostat=e_io)end_rec
837  ENDSELECT
838  RETURN
839  !--------------------------------------------------------------------------------------------------------------------------------
840  END FUNCTION vtk_geo_rect_r4
841 
842  FUNCTION vtk_geo_unst_r8(NN,X,Y,Z) RESULT(E_IO)
843  !--------------------------------------------------------------------------------------------------------------------------------
844  !! FUNCTION FOR SAVING MESH; TOPOLOGY = UNSTRUCTURED\_GRID (R8P).
845  !--------------------------------------------------------------------------------------------------------------------------------
846 
847  IMPLICIT NONE
848 
849  !--------------------------------------------------------------------------------------------------------------------------------
850  INTEGER(I4P), INTENT(IN):: NN ! NUMBER OF NODES
851  REAL(R8P), INTENT(IN):: X(1:nn) ! X COORDINATES OF ALL NODES
852  REAL(R8P), INTENT(IN):: Y(1:nn) ! Y COORDINATES OF ALL NODES
853  REAL(R8P), INTENT(IN):: Z(1:nn) ! Z COORDINATES OF ALL NODES
854  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
855  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
856  INTEGER(I4P):: N1 ! COUNTER
857  !--------------------------------------------------------------------------------------------------------------------------------
858 
859  !--------------------------------------------------------------------------------------------------------------------------------
860  SELECT CASE(f_out)
861  CASE(f_out_ascii)
862  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
863  & 'POINTS ',nn,' double'
864  WRITE(unit=unit_vtk,fmt='(3'//fr8p//')', iostat=e_io)
865  & (x(n1),y(n1),z(n1),n1=1,nn)
866  CASE(f_out_binary)
867  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
868  & 'POINTS ',nn,' double'
869  WRITE(unit=unit_vtk, iostat=e_io)
870  & trim(s_buffer)//end_rec
871  WRITE(unit=unit_vtk, iostat=e_io)
872  & (x(n1),y(n1),z(n1),n1=1,nn)
873  WRITE(unit=unit_vtk, iostat=e_io)end_rec
874  ENDSELECT
875  RETURN
876  !--------------------------------------------------------------------------------------------------------------------------------
877  END FUNCTION vtk_geo_unst_r8
878 
879  FUNCTION vtk_geo_unst_r4(NN,X,Y,Z) RESULT(E_IO)
880  !--------------------------------------------------------------------------------------------------------------------------------
881  !! FUNCTION FOR SAVING MESH; TOPOLOGY = UNSTRUCTURED\_GRID (R4P).
882  !--------------------------------------------------------------------------------------------------------------------------------
883 
884  IMPLICIT NONE
885 
886  !--------------------------------------------------------------------------------------------------------------------------------
887  INTEGER(I4P), INTENT(IN):: NN ! NUMBER OF NODES
888  REAL(R4P), INTENT(IN):: X(1:nn) ! X COORDINATES OF ALL NODES
889  REAL(R4P), INTENT(IN):: Y(1:nn) ! Y COORDINATES OF ALL NODES
890  REAL(R4P), INTENT(IN):: Z(1:nn) ! Z COORDINATES OF ALL NODES
891  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
892  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
893  INTEGER(I4P):: N1 ! COUNTER
894  !--------------------------------------------------------------------------------------------------------------------------------
895 
896  !--------------------------------------------------------------------------------------------------------------------------------
897  SELECT CASE(f_out)
898  CASE(f_out_ascii)
899  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//',A)',iostat=e_io)
900  & 'POINTS ',nn,' float'
901  WRITE(unit=unit_vtk,fmt='(3'//fr4p//')', iostat=e_io)
902  & (x(n1),y(n1),z(n1),n1=1,nn)
903  CASE(f_out_binary)
904  WRITE(s_buffer, fmt='(A,'//fi4p//',A)',iostat=e_io)
905  & 'POINTS ',nn,' float'
906  WRITE(unit=unit_vtk, iostat=e_io)
907  & trim(s_buffer)//end_rec
908  WRITE(unit=unit_vtk, iostat=e_io)
909  & (x(n1),y(n1),z(n1),n1=1,nn)
910  WRITE(unit=unit_vtk, iostat=e_io)end_rec
911  ENDSELECT
912  RETURN
913  !--------------------------------------------------------------------------------------------------------------------------------
914  END FUNCTION vtk_geo_unst_r4
915  !(DOC/)SKIPPEDBLOCK
916 
917  FUNCTION vtk_con(NC,CONNECT,CELL_TYPE) RESULT(E_IO)
918  !--------------------------------------------------------------------------------------------------------------------------------
919  !!THIS FUNCTION \MAIUSCOLETTOBS{MUST} BE USED WHEN UNSTRUCTURED GRID IS USED. IT SAVES THE CONNECTIVITY OF THE UNSTRUCTURED
920  !!MESH.
921  !--------------------------------------------------------------------------------------------------------------------------------
922 
923  IMPLICIT NONE
924 
925  !--------------------------------------------------------------------------------------------------------------------------------
926  INTEGER(I4P), INTENT(IN):: NC ! NUMBER OF CELLS
927  INTEGER(I4P), INTENT(IN):: CONNECT(:) ! MESH CONNECTIVITY
928  INTEGER(I4P), INTENT(IN):: CELL_TYPE(1:nc) ! VTK CELL TYPE
929  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
930  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
931  INTEGER(I4P):: NCON ! DIMENSION OF CONNECTIVITY VECTOR 
932  !!THE VTK\_CON VARIABLES HAVE THE FOLLOWING MEANING:
933  !!
934  !!\BEGIN{DESCRIPTION}
935  !! \ITEM[{\COLOR{ROYALBLUE}NC}] INDICATES THE NUMBER OF ALL CELLS.
936  !! \ITEM[{\COLOR{ROYALBLUE}CONNECT}] CONTAINS THE CONNECTIVITY OF THE MESH. IT IS A VECTOR.
937  !! \ITEM[{\COLOR{ROYALBLUE}CELL\_TYPE}] CONTAINS THE TYPE OF EVERY CELLS. IT IS A VECTOR OF $[1:NC]$.
938  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
939  !!\END{DESCRIPTION}
940  !!
941  !!THE VECTOR \MAIUSCOLETTOBS{CONNECT} MUST FOLLOW THE VTK LEGACY STANDARD. IT IS PASSED AS \MAIUSCOLETTOBS{ASSUMED-SHAPE} ARRAY
942  !!BECAUSE ITS DIMENSIONS IS RELATED TO THE MESH DIMENSIONS IN A COMPLEX WAY. ITS DIMENSIONS CAN BE CALCULATED BY THE FOLLOWING
943  !!EQUATION:
944  !!
945  !!\BEGIN{EQUATION}
946  !!DC = NC + \SUM\LIMITS_{I = 1}^{NC} {NVERTEX_I }
947  !!\LABEL{EQ:CONNECTIVITY DIMENSIONS}
948  !!\END{EQUATION}
949  !!
950  !!\NOINDENT WHERE $DC$ IS CONNECTIVITY VECTOR DIMENSION AND $NVERTEX_I$ IS THE NUMBER OF VERTICES OF $I^{TH}$ CELL. THE VTK
951  !!LEGACY STANDARD FOR THE MESH CONNECTIVITY IS QUITE OBSCURE AT LEAST AT FIRST SIGHT. IT IS MORE SIMPLE ANALIZING AN EXAMPLE.
952  !!SUPPOSE WE HAVE A MESH COMPOSED BY 2 CELLS, ONE HEXAHEDRON (8 VERTICES) AND ONE PYRAMID WITH SQUARE BASIS (5 VERTICES); SUPPOSE
953  !!THAT THE BASIS OF PYRAMID IS CONSTITUTE BY A FACE OF THE HEXAHEDRON AND SO THE TWO CELLS SHARE 4 VERTICES. THE EQUATION
954  !!\REF{EQ:CONNECTIVITY DIMENSIONS} GIVES $DC=2+8+5=15$; THE CONNECTIVITY VECTOR FOR THIS MESH CAN BE:
955  !!
956  !!\BEGIN{BOXRED}{CONNECTIVITY VECTOR EXAMPLE FOR VTK LEGACY STANDARD}
957  !!\BEGIN{VERBATIM}
958  !!! FIRST CELL
959  !!CONNECT(1) = 8 => NUMBER OF VERTICES OF 1° CELL
960  !!CONNECT(2) = 0 => IDENTIFICATION FLAG OF 1° VERTEX OF 1° CELL
961  !!CONNECT(3) = 1 => IDENTIFICATION FLAG OF 2° VERTEX OF 1° CELL
962  !!CONNECT(4) = 2 => IDENTIFICATION FLAG OF 3° VERTEX OF 1° CELL
963  !!CONNECT(5) = 3 => IDENTIFICATION FLAG OF 4° VERTEX OF 1° CELL
964  !!CONNECT(6) = 4 => IDENTIFICATION FLAG OF 5° VERTEX OF 1° CELL
965  !!CONNECT(7) = 5 => IDENTIFICATION FLAG OF 6° VERTEX OF 1° CELL
966  !!CONNECT(8) = 6 => IDENTIFICATION FLAG OF 7° VERTEX OF 1° CELL
967  !!CONNECT(9) = 7 => IDENTIFICATION FLAG OF 8° VERTEX OF 1° CELL
968  !!! SECOND CELL
969  !!CONNECT(10) = 5 => NUMBER OF VERTICES OF 2° CELL
970  !!CONNECT(11) = 0 => IDENTIFICATION FLAG OF 1° VERTEX OF 2° CELL
971  !!CONNECT(12) = 1 => IDENTIFICATION FLAG OF 2° VERTEX OF 2° CELL
972  !!CONNECT(13) = 2 => IDENTIFICATION FLAG OF 3° VERTEX OF 2° CELL
973  !!CONNECT(14) = 3 => IDENTIFICATION FLAG OF 4° VERTEX OF 2° CELL
974  !!CONNECT(15) = 8 => IDENTIFICATION FLAG OF 5° VERTEX OF 2° CELL
975  !!\END{VERBATIM}
976  !!\END{BOXRED}
977  !!
978  !!\NOINDENT NOTE THAT THE FIRST 4 IDENTIFICATION FLAGS OF PYRAMID VERTICES AS THE SAME OF THE FIRST 4 IDENTIFICATION FLAGS OF
979  !!THE HEXAHEDRON BECAUSE THE TWO CELLS SHARE THIS FACE. IT IS ALSO IMPORTANT TO NOTE THAT THE IDENTIFICATION FLAGS START
980  !!FORM $0$ VALUE: THIS IS IMPOSE TO THE VTK STANDARD. THE FUNCTION VTK\_CON DOES NOT CALCULATE THE CONNECTIVITY VECTOR: IT
981  !!WRITES THE CONNECTIVITY VECTOR CONFORMING THE VTK STANDARD, BUT DOES NOT CALCULATE IT. IN THE FUTURE RELEASE OF \LIBVTKIO WILL
982  !!BE INCLUDED A FUNCTION TO CALCULATE THE CONNECTIVITY VECTOR.
983  !!
984  !!THE VECTOR VARIABLE \MAIUSCOLETTOBS{TIPO} MUST CONFORM THE VTK STANDARD \FOOTNOTE{SEE THE FILE VTK-STANDARD AT THE KITWARE
985  !!HOMEPAGE.}. IT CONTAINS THE \EMPH{TYPE} OF EACH CELLS. FOR THE ABOVE EXAMPLE THIS VECTOR IS:
986  !!
987  !!\BEGIN{BOXRED}{CELL-TYPE VECTOR EXAMPLE FOR VTK LEGACY STANDARD}
988  !!\BEGIN{VERBATIM}
989  !!TIPO(1) = 12 => VTK HEXAHEDRON TYPE OF 1° CELL
990  !!TIPO(2) = 14 => VTK PYRAMID TYPE OF 2° CELL
991  !!\END{VERBATIM}
992  !!\END{BOXRED}
993  !!
994  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_CON CALLING:
995  !!
996  !!\BEGIN{BOXRED}{VTK\_CON CALLING}
997  !!\BEGIN{VERBATIM}
998  !!...
999  !!INTEGER(4), PARAMETER:: NC=2
1000  !!INTEGER(4), PARAMETER:: NVERTEX1=8
1001  !!INTEGER(4), PARAMETER:: NVERTEX2=5
1002  !!INTEGER(4), PARAMETER:: DC=NC+NVERTEX1+NVERTEX2
1003  !!INTEGER(4):: CONNECT(1:DC)
1004  !!INTEGER(4):: CELL_TYPE(1:NC)
1005  !!...
1006  !!E_IO = VTK_CON(NC,CONNECT,CELL_TYPE)
1007  !!...
1008  !!\END{VERBATIM}
1009  !!\END{BOXRED}
1010  !--------------------------------------------------------------------------------------------------------------------------------
1011 
1012  !--------------------------------------------------------------------------------------------------------------------------------
1013  ncon = SIZE(connect,1)
1014  SELECT CASE(f_out)
1015  CASE(f_out_ascii)
1016  WRITE(unit=unit_vtk,fmt='(A,2'//fi4p//')',iostat=e_io)
1017  & 'CELLS ',nc,ncon
1018  WRITE(unit=unit_vtk,fmt=fi4p, iostat=e_io)connect
1019  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//')', iostat=e_io)
1020  & 'CELL_TYPES ',nc
1021  WRITE(unit=unit_vtk,fmt=fi4p, iostat=e_io)
1022  & cell_type
1023  CASE(f_out_binary)
1024  WRITE(s_buffer, fmt='(A,2'//fi4p//')',iostat=e_io)
1025  & 'CELLS ',nc,ncon
1026  WRITE(unit=unit_vtk, iostat=e_io)
1027  & trim(s_buffer)//end_rec
1028  WRITE(unit=unit_vtk, iostat=e_io)connect
1029  WRITE(unit=unit_vtk, iostat=e_io)end_rec
1030  WRITE(s_buffer, fmt='(A,'//fi4p//')', iostat=e_io)
1031  & 'CELL_TYPES ',nc
1032  WRITE(unit=unit_vtk, iostat=e_io)
1033  & trim(s_buffer)//end_rec
1034  WRITE(unit=unit_vtk, iostat=e_io)
1035  & cell_type
1036  WRITE(unit=unit_vtk, iostat=e_io)end_rec
1037  ENDSELECT
1038  RETURN
1039  !--------------------------------------------------------------------------------------------------------------------------------
1040  END FUNCTION vtk_con
1041 
1042  FUNCTION vtk_dat(NC_NN,VAR_LOCATION) RESULT(E_IO)
1043  !--------------------------------------------------------------------------------------------------------------------------------
1044  !!THIS FUNCTION \MAIUSCOLETTOBS{MUST} BE CALLED BEFORE SAVING THE DATA RELATED TO GEOMETRIC MESH. THIS FUNCTION INITIALIZES THE
1045  !!SAVING OF DATA VARIABLES INDICATING THE \EMPH{TYPE} OF VARIABLES THAT WILL BE SAVED.
1046  !--------------------------------------------------------------------------------------------------------------------------------
1047 
1048  IMPLICIT NONE
1049 
1050  !--------------------------------------------------------------------------------------------------------------------------------
1051  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF CELLS OR NODES OF FIELD
1052  CHARACTER(*), INTENT(IN):: VAR_LOCATION ! LOCATION OF SAVING VARIABLES: CELL FOR CELL-CENTERED, NODE FOR NODE-CENTERED
1053  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1054  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
1055  !!THE VTK\_DAT VARIABLES HAVE THE FOLLOWING MEANING:
1056  !!
1057  !!\BEGIN{DESCRIPTION}
1058  !! \ITEM[{\COLOR{ROYALBLUE}NC\_NN}] INDICATES THE NUMBER OF ALL CELLS OR ALL NODES ACCORDING TO THE VALUE OF {\COLOR{ROYALBLUE}TIPO}.
1059  !! \ITEM[{\COLOR{ROYALBLUE}VAR\_LOCATION}] CONTAINS THE LOCATION-TYPE OF VARIABLES THAT WILL BE SAVED AFTER VTK\_DAT. IT IS A SCALAR AND CAB ASSUME THE FOLLOWING VALUES:
1060  !! \BEGIN{ENUMERATEABLU}
1061  !! \ITEM \EMPH{CELL} (IT IS CASE INSENSITIVE) $\RIGHTARROW$ VARIABLES WILL BE CELL-CENTERED.
1062  !! \ITEM \EMPH{NODE} (IT IS CASE INSENSITIVE) $\RIGHTARROW$ VARIABLES WILL BE NODE-CENTERED.
1063  !! \END{ENUMERATEABLU}
1064  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1065  !!\END{DESCRIPTION}
1066  !!
1067  !!OF COURSE A SINGLE FILE CAN CONTAIN BOTH CELL AND NODE CENTERED VARIABLES; IN THIS CASE THE VTK\_DAT FUNCTION MUST BE CALLED TWO TIMES, BEFORE SAVING CELL-CENTERED VARIABLES AND BEFORE SAVING NODE-CENTERED VARIABLES.
1068  !!
1069  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_DAT CALLING:
1070  !!
1071  !!\BEGIN{BOXRED}{VTK\_DAT CALLING}
1072  !!\BEGIN{VERBATIM}
1073  !!...
1074  !!E_IO = VTK_DAT(50,'NODE')
1075  !!...
1076  !!\END{VERBATIM}
1077  !!\END{BOXRED}
1078  !--------------------------------------------------------------------------------------------------------------------------------
1079 
1080  !--------------------------------------------------------------------------------------------------------------------------------
1081  SELECT CASE(f_out)
1082  CASE(f_out_ascii)
1083  SELECT CASE(trim(upper_case(var_location)))
1084  CASE('CELL')
1085  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//')',iostat=e_io)
1086  & 'CELL_DATA ',nc_nn
1087  CASE('NODE')
1088  WRITE(unit=unit_vtk,fmt='(A,'//fi4p//')',iostat=e_io)
1089  & 'POINT_DATA ',nc_nn
1090  ENDSELECT
1091  CASE(f_out_binary)
1092  SELECT CASE(trim(upper_case(var_location)))
1093  CASE('CELL')
1094  WRITE(s_buffer, fmt='(A,'//fi4p//')',iostat=e_io)
1095  & 'CELL_DATA ',nc_nn
1096  WRITE(unit=unit_vtk, iostat=e_io)
1097  & trim(s_buffer)//end_rec
1098  CASE('NODE')
1099  WRITE(s_buffer, fmt='(A,'//fi4p//')',iostat=e_io)
1100  & 'POINT_DATA ',nc_nn
1101  WRITE(unit=unit_vtk, iostat=e_io)
1102  & trim(s_buffer)//end_rec
1103  ENDSELECT
1104  ENDSELECT
1105  RETURN
1106  !--------------------------------------------------------------------------------------------------------------------------------
1107  END FUNCTION vtk_dat
1108 
1109  !!\SECTION{VTK\_VAR}
1110  !!
1111  !!VTK\_VAR IS AN INTERFACE TO 8 DIFFERENT FUNCTIONS; THERE ARE 3 FUNCTIONS FOR SCALAR VARIABLES, 3 FUNCTIONS FOR VECTORIAL
1112  !!VARIABLES AND 2 FUNCTION TEXTURE VARIABLES.
1113  !!THIS FUNCTION SAVES THE DATA VARIABLES RELATED TO GEOMETRIC MESH. THE INPUTS THAT MUST BE PASSED CHANGE DEPENDING ON THE DATA
1114  !!VARIABLES TYPE.
1115  !!
1116  !!\SUBSECTION{VTK\_VAR SCALAR DATA}
1117  !!
1118  !!\BEGIN{BOXRED}{}
1119  !!\BEGIN{LSTLISTING}[STYLE=SIGNATURE,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR SCALAR DATA SIGNATURE}]
1120  !!FUNCTION VTK_VAR(FORMATO,NC_NN,VARNAME,VAR) RESULT(E_IO)
1121  !!\END{LSTLISTING}
1122  !!\END{BOXRED}
1123  !!
1124  !!THIS KIND OF CALL IS USED TO SAVE SCALAR DATA.
1125  !!
1126  !!\BEGIN{BOXRED}{}
1127  !!\BEGIN{LSTLISTING}[STYLE=VARIABLES,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR SCALAR DATA VARIABLES}]
1128  !!INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1129  !!CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1130  !!REAL(R8P OR R4P) OR INTEGER(I4P), INTENT(IN):: VAR(1:NC_NN) ! VARIABLE TO BE SAVED
1131  !!INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1132  !!\END{LSTLISTING}
1133  !!\END{BOXRED}
1134  !!
1135  !!THE VTK\_VAR VARIABLES HAVE THE FOLLOWING MEANING:
1136  !!
1137  !!\BEGIN{DESCRIPTION}
1138  !! \ITEM[{\COLOR{ROYALBLUE}NC\_NN}] INDICATES THE NUMBER OF ALL CELLS OR ALL NODES ACCORDING TO THE VALUE OF
1139  !! {\COLOR{ROYALBLUE}TIPO} PASSED TO VTK\_DAT.
1140  !! \ITEM[{\COLOR{ROYALBLUE}VARNAME}] CONTAINS THE NAME ATTRIBUITED THE VARIABLE SAVED.
1141  !! \ITEM[{\COLOR{ROYALBLUE}VAR}] CONTAINS THE VALUES OF VARIABLES IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1142  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1143  !!\END{DESCRIPTION}
1144  !!
1145  !!NOTE THAT THE VARIABLES \TEXTTT{VAR} CAN BE PASSED BOTH AS 8-BYTE REAL KIND, 4-BYTE REAL KIND AND 4-BYTE INTEGER; THE
1146  !!DYNAMIC DISPLACEMENT INTERFACE WILL CALL THE CORRECT FUNCTION.
1147  !!
1148  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_VAR SCALAR DATA CALLING:
1149  !!
1150  !!\BEGIN{BOXRED}{VTK\_VAR SCALAR DATA CALLING}
1151  !!\BEGIN{VERBATIM}
1152  !!...
1153  !!INTEGER(4), PARAMETER:: NC_NN=100
1154  !!REAL(4):: VAR(1:NC_NN)
1155  !!...
1156  !!E_IO = VTK_VAR(NC_NN,'SCALAR DATA',VAR)
1157  !!...
1158  !!\END{VERBATIM}
1159  !!\END{BOXRED}
1160  !!
1161  !!\SUBSECTION{VTK\_VAR REAL VECTORIAL DATA}
1162  !!
1163  !!\BEGIN{BOXRED}{}
1164  !!\BEGIN{LSTLISTING}[STYLE=SIGNATURE,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR REAL VECTORIAL DATA SIGNATURE}]
1165  !!FUNCTION VTK_VAR(TIPO,NC_NN,VARNAME,VARX,VARY,VARZ) RESULT(E_IO)
1166  !!\END{LSTLISTING}
1167  !!\END{BOXRED}
1168  !!
1169  !!THIS KIND OF CALL IS USED TO SAVE REAL VECTORIAL DATA.
1170  !!
1171  !!\BEGIN{BOXRED}{}
1172  !!\BEGIN{LSTLISTING}[STYLE=VARIABLES,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR REAL VECTORIAL DATA VARIABLES}]
1173  !!CHARACTER(*), INTENT(IN):: VEC_TYPE ! VECTOR TYPE: VECT = GENERIC VECTOR , NORM = NORMAL VECTOR
1174  !!INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1175  !!CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1176  !!REAL(R8P OR R4P), INTENT(IN):: VARX(1:NC_NN) ! X COMPONENT OF VECTOR
1177  !!REAL(R8P OR R4P), INTENT(IN):: VARY(1:NC_NN) ! Y COMPONENT OF VECTOR
1178  !!REAL(R8P OR R4P), INTENT(IN):: VARZ(1:NC_NN) ! Z COMPONENT OF VECTOR
1179  !!INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1180  !!\END{LSTLISTING}
1181  !!\END{BOXRED}
1182  !!
1183  !!THE VTK\_VAR VARIABLES HAVE THE FOLLOWING MEANING:
1184  !!
1185  !!\BEGIN{DESCRIPTION}
1186  !! \ITEM [{\COLOR{ROYALBLUE}TIPO}] INDICATES THE TYPE OF VECTOR. IT CAN ASSUME THE FOLLOWING VALUE:
1187  !! \BEGIN{ENUMERATEABLU}
1188  !! \ITEM \EMPH{VECT} $\RIGHTARROW$ GENERIC VECTOR.
1189  !! \ITEM \EMPH{NORM} $\RIGHTARROW$ NORMAL VECTOR OF FACE.
1190  !! \END{ENUMERATEABLU}
1191  !! \ITEM[{\COLOR{ROYALBLUE}NC\_NN}] INDICATES THE NUMBER OF ALL CELLS OR ALL NODES ACCORDING TO THE VALUE OF
1192  !! {\COLOR{ROYALBLUE}TIPO} PASSED TO VTK\_DAT.
1193  !! \ITEM[{\COLOR{ROYALBLUE}VARNAME}] CONTAINS THE NAME ATTRIBUITED THE VARIABLE SAVED.
1194  !! \ITEM[{\COLOR{ROYALBLUE}VARX}] CONTAINS THE VALUES OF $X$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1195  !! \ITEM[{\COLOR{ROYALBLUE}VARY}] CONTAINS THE VALUES OF $Y$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1196  !! \ITEM[{\COLOR{ROYALBLUE}VARZ}] CONTAINS THE VALUES OF $Z$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1197  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1198  !!\END{DESCRIPTION}
1199  !!
1200  !!NOTE THAT THE VARIABLES \TEXTTT{VARX,VARY,VARZ} CAN BE PASSED BOTH AS 8-BYTE REAL KIND AND 4-BYTE REAL KIND; THE DYNAMIC
1201  !!DISPLACEMENT INTERFACE WILL CALL THE CORRECT FUNCTION.
1202  !!
1203  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_VAR REAL VECTORIAL DATA CALLING:
1204  !!
1205  !!\BEGIN{BOXRED}{VTK\_VAR REAL VECTORIAL DATA CALLING}
1206  !!\BEGIN{VERBATIM}
1207  !!...
1208  !!INTEGER(4), PARAMETER:: NC_NN=100
1209  !!REAL(4):: VARX(1:NC_NN)
1210  !!REAL(4):: VARZ(1:NC_NN)
1211  !!REAL(4):: VARZ(1:NC_NN)
1212  !!...
1213  !!E_IO = VTK_VAR('VECT',NC_NN,'REAL VECTORIAL DATA',...
1214  !! ...VARX,VARY,VARZ)
1215  !!...
1216  !!\END{VERBATIM}
1217  !!\END{BOXRED}
1218  !!
1219  !!\SUBSECTION{VTK\_VAR INTEGER VECTORIAL DATA}
1220  !!
1221  !!\BEGIN{BOXRED}{}
1222  !!\BEGIN{LSTLISTING}[STYLE=SIGNATURE,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR INTEGER VECTORIAL DATA SIGNATURE}]
1223  !!FUNCTION VTK_VAR(NC_NN,VARNAME,VARX,VARY,VARZ) RESULT(E_IO)
1224  !!\END{LSTLISTING}
1225  !!\END{BOXRED}
1226  !!
1227  !!THIS KIND OF CALL IS USED TO SAVE INTEGER VECTORIAL DATA.
1228  !!
1229  !!\BEGIN{BOXRED}{}
1230  !!\BEGIN{LSTLISTING}[STYLE=VARIABLES,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR INTEGER VECTORIAL DATA VARIABLES}]
1231  !!INTEGER(R4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1232  !!CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1233  !!INTEGER(R4P), INTENT(IN):: VARX(1:NC_NN) ! X COMPONENT OF VECTOR
1234  !!INTEGER(R4P), INTENT(IN):: VARY(1:NC_NN) ! Y COMPONENT OF VECTOR
1235  !!INTEGER(R4P), INTENT(IN):: VARZ(1:NC_NN) ! Z COMPONENT OF VECTOR
1236  !!INTEGER(R4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1237  !!\END{LSTLISTING}
1238  !!\END{BOXRED}
1239  !!
1240  !!THE VTK\_VAR VARIABLES HAVE THE FOLLOWING MEANING:
1241  !!
1242  !!\BEGIN{DESCRIPTION}
1243  !! \ITEM[{\COLOR{ROYALBLUE}NC\_NN}] INDICATES THE NUMBER OF ALL CELLS OR ALL NODES ACCORDING TO THE VALUE OF
1244  !! {\COLOR{ROYALBLUE}TIPO} PASSED TO VTK\_DAT.
1245  !! \ITEM[{\COLOR{ROYALBLUE}VARNAME}] CONTAINS THE NAME ATTRIBUITED THE VARIABLE SAVED.
1246  !! \ITEM[{\COLOR{ROYALBLUE}VARX}] CONTAINS THE VALUES OF $X$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1247  !! \ITEM[{\COLOR{ROYALBLUE}VARY}] CONTAINS THE VALUES OF $Y$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1248  !! \ITEM[{\COLOR{ROYALBLUE}VARZ}] CONTAINS THE VALUES OF $Z$ COMPONENT IN EACH NODES OR CELLS. IT IS A VECTOR OF $[1:NC\_NN]$.
1249  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1250  !!\END{DESCRIPTION}
1251  !!
1252  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_VAR REAL VECTORIAL DATA CALLING:
1253  !!
1254  !!\BEGIN{BOXRED}{VTK\_VAR INTEGER VECTORIAL DATA CALLING}
1255  !!\BEGIN{VERBATIM}
1256  !!...
1257  !!INTEGER(4), PARAMETER:: NC_NN=100
1258  !!INTEGER(4):: VARX(1:NC_NN)
1259  !!INTEGER(4):: VARZ(1:NC_NN)
1260  !!INTEGER(4):: VARZ(1:NC_NN)
1261  !!...
1262  !!E_IO = VTK_VAR(NC_NN,'INTEGER VECTORIAL DATA', &
1263  !! VARX,VARY,VARZ)
1264  !!...
1265  !!\END{VERBATIM}
1266  !!\END{BOXRED}
1267  !!
1268  !!\SUBSECTION{VTK\_VAR TEXTURE DATA}
1269  !!
1270  !!\BEGIN{BOXRED}{}
1271  !!\BEGIN{LSTLISTING}[STYLE=SIGNATURE,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR TEXTURE DATA SIGNATURE}]
1272  !!FUNCTION VTK_VAR(NC_NN,,DIMM,VARNAME,TEXTCOO) RESULT(E_IO)
1273  !!\END{LSTLISTING}
1274  !!\END{BOXRED}
1275  !!
1276  !!THIS KIND OF CALL IS USED TO SAVE TEXTURE DATA.
1277  !!
1278  !!\BEGIN{BOXRED}{}
1279  !!\BEGIN{LSTLISTING}[STYLE=VARIABLES,TITLE=\COLOR{MAROON}\MAIUSCOLETTOBS{VTK\_VAR TEXTURE DATA VARIABLES}]
1280  !!INTEGER(R4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1281  !!INTEGER(R4P), INTENT(IN):: DIMM ! TEXTURE DIMENSIONS
1282  !!CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1283  !!REAL(R8P OR R4P), INTENT(IN):: TEXTCOO(1:NC_NN,1:DIMM) ! TEXTURE
1284  !!INTEGER(R4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1285  !!\END{LSTLISTING}
1286  !!\END{BOXRED}
1287  !!
1288  !!THE VTK\_VAR VARIABLES HAVE THE FOLLOWING MEANING:
1289  !!
1290  !!\BEGIN{DESCRIPTION}
1291  !! \ITEM[{\COLOR{ROYALBLUE}NC\_NN}] INDICATES THE NUMBER OF ALL CELLS OR ALL NODES ACCORDING TO THE VALUE OF
1292  !! {\COLOR{ROYALBLUE}TIPO} PASSED TO VTK\_DAT.
1293  !! \ITEM[{\COLOR{ROYALBLUE}DIMM}] INDICATES THE DIMENSIONS OF THE TEXTURE COORDINATES. IT CAN ASSUME THE VALUE:
1294  !! \BEGIN{ENUMERATEABLU}
1295  !! \ITEM \EMPH{1} $\RIGHTARROW$ SCALAR TEXTURE.
1296  !! \ITEM \EMPH{2} $\RIGHTARROW$ TWODIMENSIONAL TEXTURE.
1297  !! \ITEM \EMPH{3} $\RIGHTARROW$ THREEDIMENSIONAL TEXTURE.
1298  !! \END{ENUMERATEABLU}
1299  !! \ITEM[{\COLOR{ROYALBLUE}VARNAME}] CONTAINS THE NAME ATTRIBUITED THE VARIABLE SAVED.
1300  !! \ITEM[{\COLOR{ROYALBLUE}TEXTCOO}] CONTAINS THE COORDINATES OF TEXTURE IN EACH NODES OR CELLS. IT IS A VECTOR OF
1301  !! $[1:NC\_NN,1:DIMM]$.
1302  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1303  !!\END{DESCRIPTION}
1304  !!
1305  !!NOTE THAT THE VARIABLE \TEXTTT{TEXTCOO} CAN BE PASSED BOTH AS 8-BYTE REAL KIND AND 4-BYTE REAL KIND; THE DYNAMIC
1306  !!DISPLACEMENT INTERFACE WILL CALL THE CORRECT FUNCTION.
1307  !!
1308  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_VAR TEXTURE DATA CALLING:
1309  !!
1310  !!\BEGIN{BOXRED}{VTK\_VAR TEXTURE DATA CALLING}
1311  !!\BEGIN{VERBATIM}
1312  !!...
1313  !!INTEGER(4), PARAMETER:: NC_NN=100
1314  !!INTEGER(4), PARAMETER:: DIMM=2
1315  !!REAL(4):: TEXTCOO(1:NC_NN,1:DIMM)
1316  !!...
1317  !!E_IO = VTK_VAR(NC_NN,DIMM,'TEXTURE DATA',TEXTCOO)
1318  !!...
1319  !!\END{VERBATIM}
1320  !!\END{BOXRED}
1321  !!
1322  !(\DOC)SKIPPEDBLOCK
1323  FUNCTION vtk_var_scal_r8(NC_NN,VARNAME,VAR) RESULT(E_IO)
1324  !--------------------------------------------------------------------------------------------------------------------------------
1325  !! FUNCTION FOR SAVING FIELD OF SCALAR VARIABLE (R8P).
1326  !--------------------------------------------------------------------------------------------------------------------------------
1327 
1328  IMPLICIT NONE
1329 
1330  !--------------------------------------------------------------------------------------------------------------------------------
1331  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1332  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1333  REAL(R8P), INTENT(IN):: VAR(1:nc_nn) ! VARIABLE TO BE SAVED
1334  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1335  !--------------------------------------------------------------------------------------------------------------------------------
1336 
1337  !--------------------------------------------------------------------------------------------------------------------------------
1338  SELECT CASE(f_out)
1339  CASE(f_out_ascii)
1340  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)'SCALARS '//
1341  & trim(varname)//' double 1'
1342  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
1343  & 'LOOKUP_TABLE default'
1344  WRITE(unit=unit_vtk,fmt=fr8p, iostat=e_io)var
1345  CASE(f_out_binary)
1346  WRITE(unit=unit_vtk,iostat=e_io)'SCALARS '//trim(varname)//
1347  & ' double 1'//end_rec
1348  WRITE(unit=unit_vtk,iostat=e_io)'LOOKUP_TABLE default'//
1349  & end_rec
1350  WRITE(unit=unit_vtk,iostat=e_io)var
1351  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1352  ENDSELECT
1353  RETURN
1354  !--------------------------------------------------------------------------------------------------------------------------------
1355  END FUNCTION vtk_var_scal_r8
1356 
1357  FUNCTION vtk_var_scal_r4(NC_NN,VARNAME,VAR) RESULT(E_IO)
1358  !--------------------------------------------------------------------------------------------------------------------------------
1359  !! FUNCTION FOR SAVING FIELD OF SCALAR VARIABLE (R4P).
1360  !--------------------------------------------------------------------------------------------------------------------------------
1361 
1362  IMPLICIT NONE
1363 
1364  !--------------------------------------------------------------------------------------------------------------------------------
1365  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1366  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1367  REAL(R4P), INTENT(IN):: VAR(1:nc_nn) ! VARIABLE TO BE SAVED
1368  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1369  !--------------------------------------------------------------------------------------------------------------------------------
1370 
1371  !--------------------------------------------------------------------------------------------------------------------------------
1372  SELECT CASE(f_out)
1373  CASE(f_out_ascii)
1374  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)'SCALARS '//
1375  & trim(varname)//' float 1'
1376  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
1377  & 'LOOKUP_TABLE default'
1378  WRITE(unit=unit_vtk,fmt=fr4p, iostat=e_io)var
1379  CASE(f_out_binary)
1380  WRITE(unit=unit_vtk,iostat=e_io)'SCALARS '//trim(varname)//
1381  & ' float 1'//end_rec
1382  WRITE(unit=unit_vtk,iostat=e_io)'LOOKUP_TABLE default'//
1383  & end_rec
1384  WRITE(unit=unit_vtk,iostat=e_io)var
1385  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1386  ENDSELECT
1387  RETURN
1388  !--------------------------------------------------------------------------------------------------------------------------------
1389  END FUNCTION vtk_var_scal_r4
1390 
1391  FUNCTION vtk_var_scal_i4(NC_NN,VARNAME,VAR) RESULT(E_IO)
1392  !--------------------------------------------------------------------------------------------------------------------------------
1393  !! FUNCTION FOR SAVING FIELD OF SCALAR VARIABLE (I4P).
1394  !--------------------------------------------------------------------------------------------------------------------------------
1395 
1396  IMPLICIT NONE
1397 
1398  !--------------------------------------------------------------------------------------------------------------------------------
1399  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1400  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1401  INTEGER(I4P), INTENT(IN):: VAR(1:nc_nn) ! VARIABLE TO BE SAVED
1402  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1403  !--------------------------------------------------------------------------------------------------------------------------------
1404 
1405  !--------------------------------------------------------------------------------------------------------------------------------
1406  SELECT CASE(f_out)
1407  CASE(f_out_ascii)
1408  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)'SCALARS '//
1409  & trim(varname)//' int 1'
1410  WRITE(unit=unit_vtk,fmt='(A)',iostat=e_io)
1411  & 'LOOKUP_TABLE default'
1412  WRITE(unit=unit_vtk,fmt=fi4p, iostat=e_io)var
1413  CASE(f_out_binary)
1414  WRITE(unit=unit_vtk,iostat=e_io)'SCALARS '//trim(varname)//
1415  & ' int 1'//end_rec
1416  WRITE(unit=unit_vtk,iostat=e_io)'LOOKUP_TABLE default'//
1417  & end_rec
1418  WRITE(unit=unit_vtk,iostat=e_io)var
1419  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1420  ENDSELECT
1421  RETURN
1422  !--------------------------------------------------------------------------------------------------------------------------------
1423  END FUNCTION vtk_var_scal_i4
1424 
1425  FUNCTION vtk_var_vect_r8(VEC_TYPE,NC_NN,VARNAME,VARX,VARY,VARZ)
1426  & result(e_io)
1427  !--------------------------------------------------------------------------------------------------------------------------------
1428  !! FUNCTION FOR SAVING FIELD OF VECTORIAL VARIABLE (R8P).
1429  !--------------------------------------------------------------------------------------------------------------------------------
1430 
1431  IMPLICIT NONE
1432 
1433  !--------------------------------------------------------------------------------------------------------------------------------
1434  CHARACTER(*), INTENT(IN):: VEC_TYPE ! VECTOR TYPE: VECT = GENERIC VECTOR , NORM = NORMAL VECTOR
1435  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1436  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1437  REAL(R8P), INTENT(IN):: VARX(1:nc_nn) ! X COMPONENT OF VECTOR
1438  REAL(R8P), INTENT(IN):: VARY(1:nc_nn) ! Y COMPONENT OF VECTOR
1439  REAL(R8P), INTENT(IN):: VARZ(1:nc_nn) ! Z COMPONENT OF VECTOR
1440  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1441  INTEGER(I8P):: N1 ! COUNTER
1442  !--------------------------------------------------------------------------------------------------------------------------------
1443 
1444  !--------------------------------------------------------------------------------------------------------------------------------
1445  SELECT CASE(f_out)
1446  CASE(f_out_ascii)
1447  SELECT CASE(upper_case(trim(vec_type)))
1448  CASE('VECT')
1449  WRITE(unit=unit_vtk,fmt='(A)', iostat=e_io)
1450  & 'VECTORS '//trim(varname)//' double'
1451  CASE('NORM')
1452  WRITE(unit=unit_vtk,fmt='(A)', iostat=e_io)
1453  & 'NORMALS '//trim(varname)//' double'
1454  ENDSELECT
1455  WRITE(unit=unit_vtk,fmt='(3'//fr8p//')',iostat=e_io)
1456  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1457  CASE(f_out_binary)
1458  SELECT CASE(upper_case(trim(vec_type)))
1459  CASE('VECT')
1460  WRITE(unit=unit_vtk,iostat=e_io)'VECTORS '//trim(varname)//
1461  & ' double'//end_rec
1462  CASE('NORM')
1463  WRITE(unit=unit_vtk,iostat=e_io)'NORMALS '//trim(varname)//
1464  & ' double'//end_rec
1465  ENDSELECT
1466  WRITE(unit=unit_vtk,iostat=e_io)
1467  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1468  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1469  ENDSELECT
1470  RETURN
1471  !--------------------------------------------------------------------------------------------------------------------------------
1472  END FUNCTION vtk_var_vect_r8
1473 
1474  FUNCTION vtk_var_vect_r4(VEC_TYPE,NC_NN,VARNAME,VARX,VARY,VARZ)
1475  & result(e_io)
1476  !--------------------------------------------------------------------------------------------------------------------------------
1477  !! FUNCTION FOR SAVING FIELD OF VECTORIAL VARIABLE (R4P).
1478  !--------------------------------------------------------------------------------------------------------------------------------
1479 
1480  IMPLICIT NONE
1481 
1482  !--------------------------------------------------------------------------------------------------------------------------------
1483  CHARACTER(*), INTENT(IN):: VEC_TYPE ! VECTOR TYPE: VECT = GENERIC VECTOR , NORM = NORMAL VECTOR
1484  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1485  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1486  REAL(R4P), INTENT(IN):: VARX(1:nc_nn) ! X COMPONENT OF VECTOR
1487  REAL(R4P), INTENT(IN):: VARY(1:nc_nn) ! Y COMPONENT OF VECTOR
1488  REAL(R4P), INTENT(IN):: VARZ(1:nc_nn) ! Z COMPONENT OF VECTOR
1489  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1490  INTEGER(I8P):: N1 ! COUNTER
1491  !--------------------------------------------------------------------------------------------------------------------------------
1492 
1493  !--------------------------------------------------------------------------------------------------------------------------------
1494  SELECT CASE(f_out)
1495  CASE(f_out_ascii)
1496  SELECT CASE(upper_case(trim(vec_type)))
1497  CASE('VECT')
1498  WRITE(unit=unit_vtk,fmt='(A)', iostat=e_io)
1499  & 'VECTORS '//trim(varname)//' float'
1500  CASE('NORM')
1501  WRITE(unit=unit_vtk,fmt='(A)', iostat=e_io)
1502  & 'NORMALS '//trim(varname)//' float'
1503  ENDSELECT
1504  WRITE(unit=unit_vtk,fmt='(3'//fr4p//')',iostat=e_io)
1505  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1506  CASE(f_out_binary)
1507  SELECT CASE(upper_case(trim(vec_type)))
1508  CASE('VECT')
1509  WRITE(unit=unit_vtk,iostat=e_io)'VECTORS '//trim(varname)//
1510  & ' float'//end_rec
1511  CASE('NORM')
1512  WRITE(unit=unit_vtk,iostat=e_io)'NORMALS '//trim(varname)//
1513  & ' float'//end_rec
1514  ENDSELECT
1515  WRITE(unit=unit_vtk,iostat=e_io)
1516  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1517  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1518  ENDSELECT
1519  RETURN
1520  !--------------------------------------------------------------------------------------------------------------------------------
1521  END FUNCTION vtk_var_vect_r4
1522 
1523  FUNCTION vtk_var_vect_i4(NC_NN,VARNAME,VARX,VARY,VARZ)
1524  & result(e_io)
1525  !--------------------------------------------------------------------------------------------------------------------------------
1526  !! FUNCTION FOR SAVING FIELD OF VECTORIAL VARIABLE (I4P).
1527  !--------------------------------------------------------------------------------------------------------------------------------
1528 
1529  IMPLICIT NONE
1530 
1531  !--------------------------------------------------------------------------------------------------------------------------------
1532  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1533  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1534  INTEGER(I4P), INTENT(IN):: VARX(1:nc_nn) ! X COMPONENT OF VECTOR
1535  INTEGER(I4P), INTENT(IN):: VARY(1:nc_nn) ! Y COMPONENT OF VECTOR
1536  INTEGER(I4P), INTENT(IN):: VARZ(1:nc_nn) ! Z COMPONENT OF VECTOR
1537  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1538  INTEGER(I8P):: N1 ! COUNTER
1539  !--------------------------------------------------------------------------------------------------------------------------------
1540 
1541  !--------------------------------------------------------------------------------------------------------------------------------
1542  SELECT CASE(f_out)
1543  CASE(f_out_ascii)
1544  WRITE(unit=unit_vtk,fmt='(A)', iostat=e_io)
1545  & 'VECTORS '//trim(varname)//' int'
1546  WRITE(unit=unit_vtk,fmt='(3'//fi4p//')',iostat=e_io)
1547  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1548  CASE(f_out_binary)
1549  WRITE(unit=unit_vtk,iostat=e_io)'VECTORS '//trim(varname)//
1550  & ' int'//end_rec
1551  WRITE(unit=unit_vtk,iostat=e_io)
1552  & (varx(n1),vary(n1),varz(n1),n1=1,nc_nn)
1553  WRITE(unit=unit_vtk,iostat=e_io)end_rec
1554  ENDSELECT
1555  RETURN
1556  !--------------------------------------------------------------------------------------------------------------------------------
1557  END FUNCTION vtk_var_vect_i4
1558 
1559  FUNCTION vtk_var_text_r8(NC_NN,DIMM,VARNAME,TEXTCOO)
1560  & result(e_io)
1561  !--------------------------------------------------------------------------------------------------------------------------------
1562  !! Function for saving texture variable (R8P).
1563  !--------------------------------------------------------------------------------------------------------------------------------
1564 
1565  IMPLICIT NONE
1566 
1567  !--------------------------------------------------------------------------------------------------------------------------------
1568  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1569  INTEGER(I4P), INTENT(IN):: DIMM ! TEXTURE DIMENSIONS
1570  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1571  REAL(R8P), INTENT(IN):: TEXTCOO(1:nc_nn,1:dimm) ! TEXTURE
1572  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1573  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
1574  CHARACTER(LEN=MAXLEN):: S_BUFFER2 ! BUFFER STRING
1575  INTEGER(I8P):: N1,N2 ! COUNTERS
1576  !--------------------------------------------------------------------------------------------------------------------------------
1577 
1578  !--------------------------------------------------------------------------------------------------------------------------------
1579  SELECT CASE(f_out)
1580  CASE(f_out_ascii)
1581  s_buffer2 = '(A,1X,'//fi4p//'1X,A)'
1582  WRITE(unit=unit_vtk,fmt=trim(s_buffer2), iostat=e_io)
1583  & 'TEXTURE_COORDINATES '//trim(varname),dimm,' double'
1584  WRITE(s_buffer, fmt='(I1)', iostat=e_io)
1585  & dimm
1586  s_buffer='('//trim(s_buffer)//fr4p//')'
1587  WRITE(unit=unit_vtk,fmt=trim(s_buffer), iostat=e_io)
1588  & ((textcoo(n1,n2),n2=1,dimm),n1=1,nc_nn)
1589  CASE(f_out_binary)
1590  s_buffer2 = '(A,1X,'//fi4p//'1X,A)'
1591  WRITE(s_buffer, fmt=trim(s_buffer), iostat=e_io)
1592  & 'TEXTURE_COORDINATES '//trim(varname),dimm,' double'
1593  WRITE(unit=unit_vtk, iostat=e_io)
1594  & trim(s_buffer)//end_rec
1595  WRITE(unit=unit_vtk, iostat=e_io)
1596  & ((textcoo(n1,n2),n2=1,dimm),n1=1,nc_nn)
1597  WRITE(unit=unit_vtk, iostat=e_io)
1598  & end_rec
1599  ENDSELECT
1600  RETURN
1601  !--------------------------------------------------------------------------------------------------------------------------------
1602  END FUNCTION vtk_var_text_r8
1603 
1604  FUNCTION vtk_var_text_r4(NC_NN,DIMM,VARNAME,TEXTCOO)
1605  & result(e_io)
1606  !--------------------------------------------------------------------------------------------------------------------------------
1607  !! FUNCTION FOR SAVING TEXTURE VARIABLE (R4P).
1608  !--------------------------------------------------------------------------------------------------------------------------------
1609 
1610  IMPLICIT NONE
1611 
1612  !--------------------------------------------------------------------------------------------------------------------------------
1613  INTEGER(I4P), INTENT(IN):: NC_NN ! NUMBER OF NODES OR CELLS
1614  INTEGER(I4P), INTENT(IN):: DIMM ! TEXTURE DIMENSIONS
1615  CHARACTER(*), INTENT(IN):: VARNAME ! VARIABLE NAME
1616  REAL(R4P), INTENT(IN):: TEXTCOO(1:nc_nn,1:dimm) ! TEXTURE
1617  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1618  CHARACTER(LEN=MAXLEN):: S_BUFFER ! BUFFER STRING
1619  CHARACTER(LEN=MAXLEN):: S_BUFFER2 ! BUFFER STRING
1620  INTEGER(I8P):: N1,N2 ! COUNTERS
1621  !--------------------------------------------------------------------------------------------------------------------------------
1622 
1623  !--------------------------------------------------------------------------------------------------------------------------------
1624  SELECT CASE(f_out)
1625  CASE(f_out_ascii)
1626  s_buffer2 = '(A,1X,'//fi4p//'1X,A)'
1627  WRITE(unit=unit_vtk,fmt=trim(s_buffer2), iostat=e_io)
1628  & 'TEXTURE_COORDINATES '//trim(varname),dimm,' float'
1629  WRITE(s_buffer, fmt='(I1)', iostat=e_io)
1630  & dimm
1631  s_buffer='('//trim(s_buffer)//fr4p//')'
1632  WRITE(unit=unit_vtk,fmt=trim(s_buffer), iostat=e_io)
1633  & ((textcoo(n1,n2),n2=1,dimm),n1=1,nc_nn)
1634  CASE(f_out_binary)
1635  s_buffer2 = '(A,1X,'//fi4p//'1X,A)'
1636  WRITE(s_buffer, fmt=trim(s_buffer2), iostat=e_io)
1637  & 'TEXTURE_COORDINATES '//trim(varname),dimm,' float'
1638  WRITE(unit=unit_vtk, iostat=e_io)
1639  & trim(s_buffer)//end_rec
1640  WRITE(unit=unit_vtk, iostat=e_io)
1641  & ((textcoo(n1,n2),n2=1,dimm),n1=1,nc_nn)
1642  WRITE(unit=unit_vtk, iostat=e_io)
1643  & end_rec
1644  ENDSELECT
1645  RETURN
1646  !--------------------------------------------------------------------------------------------------------------------------------
1647  END FUNCTION vtk_var_text_r4
1648  !(DOC/)SKIPPEDBLOCK
1649 
1650  FUNCTION vtk_end() RESULT(E_IO)
1651  !--------------------------------------------------------------------------------------------------------------------------------
1652  !!THIS FUNCTION IS USED TO FINALIZE THE FILE OPENED AND IT HAS NOT INPUTS. THE \LIBVTKIO MANAGES THE FILE UNIT WITHOUT THE
1653  !!USER'S ACTION.
1654  !--------------------------------------------------------------------------------------------------------------------------------
1655 
1656  IMPLICIT NONE
1657 
1658  !--------------------------------------------------------------------------------------------------------------------------------
1659  INTEGER(I4P):: E_IO ! INPUT/OUTPUT INQUIRING FLAG: $0$ IF IO IS DONE, $> 0$ IF IO IS NOT DONE
1660  !!THE VTK\_END VARIABLES HAVE THE FOLLOWING MEANING:
1661  !!
1662  !!\BEGIN{DESCRIPTION}
1663  !! \ITEM[{\COLOR{ROYALBLUE}E\_IO}] CONTAINS THE INQUIRING INTEGER FLAG FOR ERROR HANDLING.
1664  !!\END{DESCRIPTION}
1665  !!
1666  !!THE FOLLOWING IS AN EXAMPLE OF VTK\_END CALLING:
1667  !!
1668  !!\BEGIN{BOXRED}{VTK\_END CALLING}
1669  !!\BEGIN{VERBATIM}
1670  !!...
1671  !!E_IO = VTK_END()
1672  !!...
1673  !!\END{VERBATIM}
1674  !!\END{BOXRED}
1675  !--------------------------------------------------------------------------------------------------------------------------------
1676 
1677  !--------------------------------------------------------------------------------------------------------------------------------
1678  CLOSE(unit=unit_vtk,iostat=e_io)
1679  RETURN
1680  !--------------------------------------------------------------------------------------------------------------------------------
1681  END FUNCTION vtk_end
1682 
1683  !!\chapter{VTK XML functions}
1684  !!\minitoc
1685  !!\vspace*{8mm}
1686  !!
1687  !!\lettrine[lines=2,loversize=-.1,lraise=0.2]{{\bf T}}{he} XML standard is more powerful than legacy one. It is more flexible
1688  !!and free but on the other hand is more (but not so more using a library like \LIBVTKIO...) complex than legacy standard. The
1689  !!output of XML functions is a well-formated XML file at least for the ascii format (in the binary format \LIBVTKIO use
1690  !!raw-data format that does not produce a well formated XML file).
1691  !!
1692  !!The XML functions follow the same calling-convention of the legacy functions; all the \LIBVTKIO XML functions are
1693  !!\MaiuscolettoBS{4-byte integer function}: the output of these functions is an integer that is $0$ if the function calling
1694  !!has been done right while it is $> 0$ if some errors occur. The functions calling is the same as legacy functions:
1695  !!
1696  !!\begin{boxred}{Functions Calling}
1697  !!\begin{verbatim}
1698  !!...
1699  !!integer(4):: E_IO
1700  !!...
1701  !!E_IO = VTK_INI_XML(....
1702  !!...
1703  !!\end{verbatim}
1704  !!\end{boxred}
1705  !!
1706  !!\noindent Note that the XML functions have the same name of legacy functions with the suffix \virgo{\_XML}.
1707  !!
1708 #endif
1709  END MODULE lib_vtk_io
1710  !!
1711  !!\appendix
1712  !!
1713  !!\chapter{LIB\_VTK\_IO Usage Example}
1714  !!\label{cap:example}
1715  !!\minitoc
1716  !!
1717  !!\vspace*{8mm}
1718  !!
1719  !!\lettrine[lines=2,loversize=-.1,lraise=0.2]{{\bf T}}{he} usage of \LIBVTKIO is quite simple. In this chapter there are some
1720  !!example of \LIBVTKIO usage. Some of the following examples are present also in the file \MaiuscolettoBS{Test\_LIB\_VTK\_IO.f90}
1721  !!distributed within the \LIBVTKIO.
1722  !!
1723  !!\section{Legacy Rectilinear Grid}
1724  !!\label{sec:example LRECTG}
1725  !!
1726  !!\begin{boxred}{Legacy Rectilinear Grid}
1727  !!\begin{verbatim}
1728  !!...
1729  !!integer(4), intent(IN):: NX
1730  !!real(8), intent(IN):: p(1:NX)
1731  !!real(8), intent(IN):: rho(1:NX)
1732  !!real(8), intent(IN):: u(1:NX)
1733  !!real(8), intent(IN):: gamma(1:NX)
1734  !!character(*), intent(IN):: filename
1735  !!real(8):: x(1:NX)
1736  !!integer(4):: i
1737  !!...
1738  !!x=(/(i, i=1, NX, 1)/)
1739  !!E_IO = VTK_INI(output_format = 'ascii', &
1740  !! filene = trim(filename)//'.vtk', &
1741  !! title = 'Field', &
1742  !! mesh_topology = 'RECTILINEAR_GRID')
1743  !!E_IO = VTK_GEO(NX = NX, &
1744  !! NY = 1, &
1745  !! NZ = 1, &
1746  !! X = x, &
1747  !! Y = (/0.0_8/), &
1748  !! Z = (/0.0_8/))
1749  !!E_IO = VTK_DAT(NC_NN = NX, &
1750  !! tipo = 'node')
1751  !!E_IO = VTK_VAR(NC_NN = NX, &
1752  !! varname = 'p', &
1753  !! var = p)
1754  !!E_IO = VTK_VAR(NC_NN = NX, &
1755  !! varname = 'rho', &
1756  !! var = rho)
1757  !!E_IO = VTK_VAR(NC_NN = NX, &
1758  !! varname = 'u', &
1759  !! var = u)
1760  !!E_IO = VTK_VAR(NC_NN = NX, &
1761  !! varname = 'gamma', &
1762  !! var = gamma)
1763  !!E_IO = VTK_VAR(NC_NN = NX, &
1764  !! varname = 'a', &
1765  !! var = sqrt(gamma*p/rho))
1766  !!E_IO = VTK_END()
1767  !!...
1768  !!\end{verbatim}
1769  !!\end{boxred}
1770  !!
1771  !!\section{XML Rectilinear Grid}
1772  !!\label{sec:example XRECTG}
1773  !!
1774  !!\begin{boxred}{XML Rectilinear Grid}
1775  !!\begin{verbatim}
1776  !!...
1777  !!integer(4), intent(IN):: n
1778  !!integer(4), intent(IN):: NX
1779  !!real(8), intent(IN):: p(1:NX)
1780  !!real(8), intent(IN):: rho(1:NX)
1781  !!real(8), intent(IN):: u(1:NX)
1782  !!real(8), intent(IN):: gamma(1:NX)
1783  !!character(*), intent(IN):: filename
1784  !!real(8):: x(1:NX)
1785  !!integer(4):: i
1786  !!...
1787  !!x=(/(i, i=1, NX, 1)/)
1788  !!E_IO = VTK_INI_XML(output_format = 'ascii', &
1789  !! filename = trim(filename)//'.vtr', &
1790  !! mesh_topology = 'RectilinearGrid', &
1791  !! nx1=1,nx2=NX,ny1=1,ny2=1,nz1=1,nz2=1)
1792  !!E_IO = VTK_GEO_XML(nx1=1,nx2=NX,ny1=1,ny2=1,nz1=1,nz2=1, &
1793  !! X=x,Y=(/0.0_8/),Z=(/0.0_8/))
1794  !!E_IO = VTK_DAT_XML(tipo = 'node', &
1795  !! azione = 'OPEN')
1796  !!E_IO = VTK_VAR_XML(NC_NN = NX, &
1797  !! varname = 'p', &
1798  !! var = p)
1799  !!E_IO = VTK_VAR_XML(NC_NN = NX, &
1800  !! varname = 'rho', &
1801  !! var = rho)
1802  !!E_IO = VTK_VAR_XML(NC_NN = NX, &
1803  !! varname = 'u', &
1804  !! var = u)
1805  !!E_IO = VTK_VAR_XML(NC_NN = NX, &
1806  !! varname = 'gamma', &
1807  !! var = gamma)
1808  !!E_IO = VTK_VAR_XML(NC_NN = NX, &
1809  !! varname = 'a', &
1810  !! var = sqrt(gamma*p/rho))
1811  !!E_IO = VTK_DAT_XML(tipo = 'node', &
1812  !! azione = 'CLOSE')
1813  !!E_IO = VTK_GEO_XML()
1814  !!E_IO = VTK_END_XML()
1815  !!...
1816  !!\end{verbatim}
1817  !!\end{boxred}
1818  !!
1819  !!\section{Legacy Unstructured Grid}
1820  !!\label{sec:example LUNSTG}
1821  !!
1822  !!\begin{boxred}{Legacy Unstructured Grid}
1823  !!\begin{verbatim}
1824  !!...
1825  !!integer(4), parameter:: Nn = 27
1826  !!integer(4), parameter:: Ne = 11
1827  !!real(4), dimension(1:Nn):: x_uns
1828  !!real(4), dimension(1:Nn):: y_uns
1829  !!real(4), dimension(1:Nn):: z_uns
1830  !!integer(4), dimension(1:Ne):: tipo
1831  !!integer(4), dimension(1:60):: connect
1832  !!real(8), dimension(1:Nn):: var_uns_grid
1833  !!integer(4), dimension(1:Nn):: var_uns_grid_X
1834  !!integer(4), dimension(1:Nn):: var_uns_grid_Y
1835  !!integer(4), dimension(1:Nn):: var_uns_grid_Z
1836  !!...
1837  !!E_IO = VTK_INI(output_format = 'BINARY', &
1838  !! filename = 'UNST_GRID_BIN.vtk', &
1839  !! title = 'Unstructured Grid Example' &
1840  !! mesh_topology = 'UNSTRUCTURED_GRID')
1841  !!
1842  !!x_uns=(/0,1,2,0,1,2, &
1843  !! 0,1,2,0,1,2, &
1844  !! 0,1,2,0,1,2, &
1845  !! 0,1,2,0,1,2, &
1846  !! 0,1,2/)
1847  !!y_uns=(/0,0,0,1,1,1, &
1848  !! 0,0,0,1,1,1, &
1849  !! 1,1,1,1,1,1, &
1850  !! 1,1,1,1,1,1, &
1851  !! 1,1,1/)
1852  !!z_uns=(/0,0,0,0,0,0, &
1853  !! 1,1,1,1,1,1, &
1854  !! 2,2,2,3,3,3, &
1855  !! 4,4,4,5,5,5, &
1856  !! 6,6,6/)
1857  !!
1858  !!E_IO = VTK_GEO(Nnodi = Nn, &
1859  !! X=x_uns,Y=y_uns,Z=z_uns)
1860  !!
1861  !!connect = (/ 8, 0, 1, 4, 3, 6, 7,10, 9, &
1862  !! 8, 1, 2, 5, 4, 7, 8,11,10, &
1863  !! 4, 6,10, 9,12, &
1864  !! 4, 5,11,10,14, &
1865  !! 6,15,16,17,14,13,12, &
1866  !! 6,18,15,19,16,20,17, &
1867  !! 4,22,23,20,19, &
1868  !! 3,21,22,18, &
1869  !! 3,22,19,18, &
1870  !! 2,26,25, &
1871  !! 1,24/)
1872  !!tipo = (/12, &
1873  !! 12, &
1874  !! 10, &
1875  !! 10, &
1876  !! 7, &
1877  !! 6, &
1878  !! 9, &
1879  !! 5, &
1880  !! 5, &
1881  !! 3, &
1882  !! 1/)
1883  !!E_IO = VTK_CON(NCelle = Ne, &
1884  !! connect = connect, &
1885  !! tipo = tipo)
1886  !!E_IO = VTK_DAT(NC_NN = Nn, &
1887  !! tipo = 'node')
1888  !!
1889  !!var_uns_grid =(/ 0.0, 1.0, 2.0, 3.0, 4.0, 5.0, &
1890  !! 6.0, 7.0, 8.0, 9.0,10.0,11.0, &
1891  !! 12.0,13.0,14.0,15.0,16.0,17.0, &
1892  !! 18.0,19.0,20.0,21.0,22.0,23.0, &
1893  !! 24.0,25.0,26.0/)
1894  !!
1895  !!E_IO = VTK_VAR(NC_NN = Nn, &
1896  !! varname = 'scalars', &
1897  !! var = var_uns_grid)
1898  !!
1899  !!var_uns_grid_X=(/1,1,0,1,1,0, &
1900  !! 1,1,0,1,1,0, &
1901  !! 0,0,0,0,0,0, &
1902  !! 0,0,0,0,0,0, &
1903  !! 0,0,0/)
1904  !!var_uns_grid_Y=(/0,1,2,0,1,2, &
1905  !! 0,1,2,0,1,2, &
1906  !! 0,0,0,0,0,0, &
1907  !! 0,0,0,0,0,0, &
1908  !! 0,0,0/)
1909  !!var_uns_grid_Z=(/0,0,0,0,0,0, &
1910  !! 0,0,0,0,0,0, &
1911  !! 1,1,1,1,1,1, &
1912  !! 1,1,1,1,1,1, &
1913  !! 1,1,1/)
1914  !!E_IO = VTK_VAR(NC_NN = Nn, &
1915  !! varname = 'vectors', &
1916  !! varX = var_uns_grid_X, &
1917  !! varY = var_uns_grid_Y, &
1918  !! varZ = var_uns_grid_Z)
1919  !!E_IO = VTK_END()
1920  !!...
1921  !!\end{verbatim}
1922  !!\end{boxred}
1923  !!
1924  !!\section{XML Unstructured Grid}
1925  !!\label{sec:example XUNSTG}
1926  !!
1927  !!\begin{boxred}{XML Unstructured Grid}
1928  !!\begin{verbatim}
1929  !!...
1930  !!integer(4), parameter:: Nn = 27
1931  !!integer(4), parameter:: Ne = 11
1932  !!real(4), dimension(1:Nn):: x_uns
1933  !!real(4), dimension(1:Nn):: y_uns
1934  !!real(4), dimension(1:Nn):: z_uns
1935  !!integer(4), dimension(1:Ne):: tipo
1936  !!integer(4), dimension(1:49):: connect_xml
1937  !!integer(4), dimension(1:Ne):: offset_xml
1938  !!real(8), dimension(1:Nn):: var_uns_grid
1939  !!integer(4), dimension(1:Nn):: var_uns_grid_X
1940  !!integer(4), dimension(1:Nn):: var_uns_grid_Y
1941  !!integer(4), dimension(1:Nn):: var_uns_grid_Z
1942  !!...
1943  !!E_IO = VTK_INI_XML(output_format = 'BINARY', &
1944  !! filename = 'XML_UNST_BINARY.vtu', &
1945  !! mesh_topology = 'UnstructuredGrid')
1946  !!
1947  !!x_uns=(/0,1,2,0,1,2, &
1948  !! 0,1,2,0,1,2, &
1949  !! 0,1,2,0,1,2, &
1950  !! 0,1,2,0,1,2, &
1951  !! 0,1,2/)
1952  !!y_uns=(/0,0,0,1,1,1, &
1953  !! 0,0,0,1,1,1, &
1954  !! 1,1,1,1,1,1, &
1955  !! 1,1,1,1,1,1, &
1956  !! 1,1,1/)
1957  !!z_uns=(/0,0,0,0,0,0, &
1958  !! 1,1,1,1,1,1, &
1959  !! 2,2,2,3,3,3, &
1960  !! 4,4,4,5,5,5, &
1961  !! 6,6,6/)
1962  !!
1963  !!E_IO = VTK_GEO_XML(Nnodi = Nn, &
1964  !! NCelle = Ne, &
1965  !! X=x_uns,Y=y_uns,Z=z_uns)
1966  !!
1967  !!connect_xml = (/ 0, 1, 4, 3, 6, 7,10, 9, &
1968  !! 1, 2, 5, 4, 7, 8,11,10, &
1969  !! 6,10, 9,12, &
1970  !! 5,11,10,14, &
1971  !! 15,16,17,14,13,12, &
1972  !! 18,15,19,16,20,17, &
1973  !! 22,23,20,19, &
1974  !! 21,22,18, &
1975  !! 22,19,18, &
1976  !! 26,25, &
1977  !! 24/)
1978  !!offset_xml = (/ 8, &
1979  !! 16, &
1980  !! 20, &
1981  !! 24, &
1982  !! 30, &
1983  !! 36, &
1984  !! 40, &
1985  !! 43, &
1986  !! 46, &
1987  !! 48, &
1988  !! 49/)
1989  !!
1990  !!E_IO = VTK_CON_XML(NCelle = Ne, &
1991  !! connect = connect_xml, &
1992  !! offset = offset_xml, &
1993  !! tipo = (/12_1, &
1994  !! 12_1, &
1995  !! 10_1, &
1996  !! 10_1, &
1997  !! 7_1, &
1998  !! 6_1, &
1999  !! 9_1, &
2000  !! 5_1, &
2001  !! 5_1, &
2002  !! 3_1, &
2003  !! 1_1/))
2004  !!
2005  !!E_IO = VTK_DAT_XML(tipo = 'node', &
2006  !! azione = 'OPEN')
2007  !!
2008  !!var_uns_grid =(/ 0.0, 1.0, 2.0, 3.0, 4.0, 5.0, &
2009  !! 6.0, 7.0, 8.0, 9.0,10.0,11.0, &
2010  !! 12.0,13.0,14.0,15.0,16.0,17.0, &
2011  !! 18.0,19.0,20.0,21.0,22.0,23.0, &
2012  !! 24.0,25.0,26.0/)
2013  !!
2014  !!E_IO = VTK_VAR_XML(NC_NN = Nn, &
2015  !! varname = 'scalars', &
2016  !! var = var_uns_grid)
2017  !!
2018  !!var_uns_grid_X=(/1,1,0,1,1,0, &
2019  !! 1,1,0,1,1,0, &
2020  !! 0,0,0,0,0,0, &
2021  !! 0,0,0,0,0,0, &
2022  !! 0,0,0/)
2023  !!var_uns_grid_Y=(/0,1,2,0,1,2, &
2024  !! 0,1,2,0,1,2, &
2025  !! 0,0,0,0,0,0, &
2026  !! 0,0,0,0,0,0, &
2027  !! 0,0,0/)
2028  !!var_uns_grid_Z=(/0,0,0,0,0,0, &
2029  !! 0,0,0,0,0,0, &
2030  !! 1,1,1,1,1,1, &
2031  !! 1,1,1,1,1,1, &
2032  !! 1,1,1/)
2033  !!
2034  !!E_IO = VTK_VAR_XML(NC_NN = Nn, &
2035  !! varname = 'vector', &
2036  !! varX = var_uns_grid_X, &
2037  !! varY = var_uns_grid_Y, &
2038  !! varZ = var_uns_grid_Z)
2039  !!E_IO = VTK_DAT_XML(tipo = 'node', &
2040  !! azione = 'CLOSE')
2041  !!E_IO = VTK_GEO_XML()
2042  !!E_IO = VTK_END_XML()
2043  !!...
2044  !!\end{verbatim}
2045  !!\end{boxred}
2046  !!
2047  !!\chapter{Fortran \& Portable-Kind-Precision Selection}
2048  !!\label{cap:kind precision}
2049  !!
2050  !!\lettrine[lines=2,loversize=-.1,lraise=0.2]{{\bf F}}{ortran} is the most popular programming language for scientific computing.
2051  !!With fortran it is quite simple obtain fast code and manage large multidimensional array. Because fortran permits the achivment
2052  !!of high performance it is also used on great range of different computer-architettures, and often on the fastest supercomputer
2053  !!in the world. Therefore fortran programs must be \MaiuscolettoBS{portable}: portability means that the code will give the same
2054  !!results on every different computer-architettures. One of the most important goal of the numeric code is to control the
2055  !!\MaiuscolettoBS{the numeric error} due to finite precision of numerical operations. Fortran uses the \MaiuscolettoBS{IEEE
2056  !!rappresentations}; integers and reals (floating point) are represented with a finite precision. So when the code computes an
2057  !!operation it has a \MaiuscolettoBS{trunction error} due to the truncation of the numerical finite rappresentaions. For numerical
2058  !!and more in general scientific applications this source of errors must be controlled. The programmer must know which is the
2059  !!precision associated to the code variables. Before the standard fortran 90/95 there are not any way to select the precision of
2060  !!the numerical variables in a portable fashion. With the possibility to specify a kind parameter for variables, the standard
2061  !!fortran 90/95 makes avaible two useful functions to select the kind precision of integers and reals:
2062  !!
2063  !!\begin{boxred}{selected\_real\_kind \& selected\_int\_kind}
2064  !!\begin{verbatim}
2065  !!function selected_real_kind(p,r) result(kind_id)
2066  !!integer, intent(IN), optional:: p
2067  !!integer, intent(IN), optional:: r
2068  !!integer:: kind_id
2069  !!
2070  !!The result, kind_id, is a scalar of type default integer.
2071  !!If both arguments are absent, the result is zero.
2072  !!Otherwise, the result has a value equal to a value of
2073  !!the kind parameter of a real data type with decimal
2074  !!precision, as returned by the function PRECISION, of at
2075  !!least p digits and a decimal exponent range, as returned
2076  !!by the function RANGE, of at least r.
2077  !!
2078  !!function selected_int_kind(p) result(kind_id)
2079  !!integer, intent(IN), optional:: p
2080  !!integer:: kind_id
2081  !!
2082  !!The result, kind_id, is a scalar of type default integer.
2083  !!The result has a value equal to the value of the kind
2084  !!parameter of the integer data type that represents all
2085  !!values n in the range of about values n with
2086  !!-10^p < n < 10^p.
2087  !!\end{verbatim}
2088  !!\end{boxred}
2089  !!
2090  !!Using these two functions the programmer can accurately control the precision of its own variables in a portable manner.
2091  !!Note that specifing the kind precision without using these two functions is not portable: $real(8)$ means different
2092  !!precisions on different architettures. Parametrizing the kind of all numerical variables using these two functions makes
2093  !!the portable. The \LIBVTKIO uses this principle to achive portable-kind-precision selection; in the library are defined
2094  !!some parameters by which all variables kind-precisions are parametrized:
2095  !!
2096  !!\begin{boxblu}{\LIBVTKIO Kind-Precision Parameters}
2097  !!{\color{RoyalBlue}\MaiuscolettoS{Real Precision Definitions}}
2098  !!\begin{description}
2099  !! \item [{\color{RoyalBlue}R16P}] real with $33$ digits, range $[+-10^{-4931},+-10^{+4931}-1]$
2100  !! \item [{\color{RoyalBlue}R8P}] real with $15$ digits, range $[+-10^{-307} ,+-10^{+307}-1 ]$
2101  !! \item [{\color{RoyalBlue}R4P}] real with $6$ digits, range $[+-10^{-37} ,+-10^+{37}-1 ]$
2102  !!\end{description}
2103  !!{\color{RoyalBlue}\MaiuscolettoS{Integer Precision Definitions}}
2104  !!\begin{description}
2105  !! \item [{\color{RoyalBlue}I8P}] range $[-2^{63},+2^{63}-1]$
2106  !! \item [{\color{RoyalBlue}I4P}] range $[-2^{31},+2^{31}-1]$
2107  !! \item [{\color{RoyalBlue}I2P}] range $[-2^{15},+2^{15}-1]$
2108  !! \item [{\color{RoyalBlue}I1P}] range $[-2^{7} ,+2^{7} -1]$
2109  !!\end{description}
2110  !!\end{boxblu}
2111  !!
2112  !!In order to avoid strange results porting your code the use of parametrized-kind-precision is very useful. The \LIBVTKIO
2113  !!makes avaible to the external its own kind-parameters that can be used to parametrize the code.
2114  !!
2115  !!\chapter{Dynamic Dispatching}
2116  !!\label{cap:Dynamic Dispatching}
2117  !!
2118  !!\lettrine[lines=2,loversize=-.1,lraise=0.2]{{\bf F}}{ortran} is not an \MaiuscolettoBS{object oriented} (OOp) programming
2119  !!language. It is a procedural language with some of the the goals (ineritance, user-definited data type, polimorphism...)
2120  !!of OOp. Fortran most important aim is to ensure the performance of the code not its \virgo{friendliness}... Despite its
2121  !!nature, fortran 90/95 makes avaible some interesting features: it permits the dynamic dispatching of functions and
2122  !!subroutine ensuring the best performance. This goal is achived with use of $interface$ construct. In the \LIBVTKIO there are,
2123  !!at today, 4 interface blocks:
2124  !!
2125  !!\begin{boxred}{\LIBVTKIO Interface Blocks}
2126  !!\begin{verbatim}
2127  !!interface VTK_GEO
2128  !! module procedure VTK_GEO_UNST_R8, &
2129  !! VTK_GEO_UNST_R4, &
2130  !! VTK_GEO_STRP_R8, &
2131  !! VTK_GEO_STRP_R4, &
2132  !! VTK_GEO_STRG_R8, &
2133  !! VTK_GEO_STRG_R4, &
2134  !! VTK_GEO_RECT_R8, &
2135  !! VTK_GEO_RECT_R4
2136  !!endinterface
2137  !!
2138  !!interface VTK_VAR
2139  !! module procedure VTK_VAR_SCAL_R8, &
2140  !! VTK_VAR_SCAL_R4, &
2141  !! VTK_VAR_SCAL_I4, &
2142  !! VTK_VAR_VECT_R8, &
2143  !! VTK_VAR_VECT_R4, &
2144  !! VTK_VAR_VECT_I4, &
2145  !! VTK_VAR_TEXT_R8, &
2146  !! VTK_VAR_TEXT_R4
2147  !!endinterface
2148  !!
2149  !!interface VTK_GEO_XML
2150  !! module procedure VTK_GEO_XML_STRG_R4, &
2151  !! VTK_GEO_XML_STRG_R8, &
2152  !! VTK_GEO_XML_RECT_R8, &
2153  !! VTK_GEO_XML_RECT_R4, &
2154  !! VTK_GEO_XML_UNST_R8, &
2155  !! VTK_GEO_XML_UNST_R4, &
2156  !! VTK_GEO_XML_CLOSEP
2157  !!endinterface
2158  !!
2159  !!interface VTK_VAR_XML
2160  !! module procedure VTK_VAR_XML_SCAL_R8, &
2161  !! VTK_VAR_XML_SCAL_R4, &
2162  !! VTK_VAR_XML_SCAL_I8, &
2163  !! VTK_VAR_XML_SCAL_I4, &
2164  !! VTK_VAR_XML_SCAL_I2, &
2165  !! VTK_VAR_XML_SCAL_I1, &
2166  !! VTK_VAR_XML_VECT_R8, &
2167  !! VTK_VAR_XML_VECT_R4, &
2168  !! VTK_VAR_XML_VECT_I8, &
2169  !! VTK_VAR_XML_VECT_I4, &
2170  !! VTK_VAR_XML_VECT_I2, &
2171  !! VTK_VAR_XML_VECT_I1
2172  !!endinterface
2173  !!\end{verbatim}
2174  !!\end{boxred}
2175  !!
2176  !!By the interface construct \LIBVTKIO has a more simple API. The user deals with a few functions without non-sense-long-name...
2177  !!Dynamic dispatching is not the magic wand to solve all problems but it is an useful tool to simplify the code API. It is
2178  !!not powerful as the C++ template, but it is a \MaiuscolettoBS{quantum-leap} for fortran programmers.
2179  !!
2180  !!\chapter{Known Bugs}
2181  !!\label{cap:BUG}
2182  !!
2183  !!\lettrine[lines=2,loversize=-.1,lraise=0.2]{{\bf T}}{he} \LIBVTKIO is a very young project and it is a good example of wrong
2184  !!programming style... It is unstable and not tested. It is used by only one user (... me of course!) and there are a lot of
2185  !!bugs that are still hidden. At the moment several features are missing (the input functions and the poly-data topology...),
2186  !!but it is useful to export fortran data to VTK standard, and this goal was the most important for me.
2187  !!
2188  !!At today only one main bug was found. Fortran allows the automatic reshape of arrays: as an example 2D array can be
2189  !!automatically (in the function calling) transformed to a 1D array with the same number of element of 2D array. The use of
2190  !!dynamic dispatching had disable this feature: dynamic dispatching use the array-shape information to dectet, at compile-time,
2191  !!the correct function to be called. So reshape arrays at calling phase is not allowed. In the next release I will fix this bug
2192  !!introducing the function to reshape arrays between 1D, 2D and 3D arrays.
2193  !!
2194  !!A possible, not already found, bug is the non correct kind detection. It is possible that a code uses kind-precision parameter
2195  !!that does not match the \LIBVTKIO parameters. I never observe this bug but it is possible. To avoid it the simple way is to use
2196  !!always the \LIBVTKIO kind-precision parameters; if the parameters actually present do not match your necessities, define new
2197  !!parameters in \LIBVTKIO and redistribuite \LIBVTKIO with your pacth!
2198  !!
2199  !!Finally there is a strong inefficiency when saving XML binary file. To write XML binary \LIBVTKIO uses a temporary scratch file
2200  !!to save binary data while saving all formatting data to the final XML file; only when all XML formatting data have been written
2201  !!the scratch file is rewinded and the binary data is saved in the final tag of XML file as \MaiuscolettoBS{raw} data. This
2202  !!algorithm is obviously inefficient. Any tip is welcome!
2203  !!
2204  !!\chapter{GNU GENERAL PUBLIC LICENSE}
2205  !!\label{cap:GPL}
2206  !!
2207  !!\begin{center}
2208  !!\MaiuscolettoS{Version 3, 29 June 2007}
2209  !!
2210  !!{\parindent 0in
2211  !!
2212  !!Copyright \copyright\ 2007 Free Software Foundation, Inc. \texttt{http://fsf.org/}
2213  !!
2214  !!\bigskip
2215  !!Everyone is permitted to copy and distribute verbatim copies of this
2216  !!
2217  !!license document, but changing it is not allowed.}
2218  !!
2219  !!\end{center}
2220  !!
2221  !!
2222  !!\section*{Preamble}
2223  !!The GNU General Public License is a free, copyleft license for
2224  !!software and other kinds of works.
2225  !!
2226  !!The licenses for most software and other practical works are designed
2227  !!to take away your freedom to share and change the works. By contrast,
2228  !!the GNU General Public License is intended to guarantee your freedom to
2229  !!share and change all versions of a program--to make sure it remains free
2230  !!software for all its users. We, the Free Software Foundation, use the
2231  !!GNU General Public License for most of our software; it applies also to
2232  !!any other work released this way by its authors. You can apply it to
2233  !!your programs, too.
2234  !!
2235  !!When we speak of free software, we are referring to freedom, not
2236  !!price. Our General Public Licenses are designed to make sure that you
2237  !!have the freedom to distribute copies of free software (and charge for
2238  !!them if you wish), that you receive source code or can get it if you
2239  !!want it, that you can change the software or use pieces of it in new
2240  !!free programs, and that you know you can do these things.
2241  !!
2242  !!To protect your rights, we need to prevent others from denying you
2243  !!these rights or asking you to surrender the rights. Therefore, you have
2244  !!certain responsibilities if you distribute copies of the software, or if
2245  !!you modify it: responsibilities to respect the freedom of others.
2246  !!
2247  !!For example, if you distribute copies of such a program, whether
2248  !!gratis or for a fee, you must pass on to the recipients the same
2249  !!freedoms that you received. You must make sure that they, too, receive
2250  !!or can get the source code. And you must show them these terms so they
2251  !!know their rights.
2252  !!
2253  !!Developers that use the GNU GPL protect your rights with two steps:
2254  !!(1) assert copyright on the software, and (2) offer you this License
2255  !!giving you legal permission to copy, distribute and/or modify it.
2256  !!
2257  !!For the developers' and authors' protection, the GPL clearly explains
2258  !!that there is no warranty for this free software. For both users' and
2259  !!authors' sake, the GPL requires that modified versions be marked as
2260  !!changed, so that their problems will not be attributed erroneously to
2261  !!authors of previous versions.
2262  !!
2263  !!Some devices are designed to deny users access to install or run
2264  !!modified versions of the software inside them, although the manufacturer
2265  !!can do so. This is fundamentally incompatible with the aim of
2266  !!protecting users' freedom to change the software. The systematic
2267  !!pattern of such abuse occurs in the area of products for individuals to
2268  !!use, which is precisely where it is most unacceptable. Therefore, we
2269  !!have designed this version of the GPL to prohibit the practice for those
2270  !!products. If such problems arise substantially in other domains, we
2271  !!stand ready to extend this provision to those domains in future versions
2272  !!of the GPL, as needed to protect the freedom of users.
2273  !!
2274  !!Finally, every program is threatened constantly by software patents.
2275  !!States should not allow patents to restrict development and use of
2276  !!software on general-purpose computers, but in those that do, we wish to
2277  !!avoid the special danger that patents applied to a free program could
2278  !!make it effectively proprietary. To prevent this, the GPL assures that
2279  !!patents cannot be used to render the program non-free.
2280  !!
2281  !!The precise terms and conditions for copying, distribution and
2282  !!modification follow.
2283  !!
2284  !!
2285  !!\begin{center}
2286  !!{\Large \sc Terms and Conditions}
2287  !!\end{center}
2288  !!
2289  !!\begin{enumerate}
2290  !!
2291  !!\addtocounter{enumi}{-1}
2292  !!
2293  !!\item Definitions.
2294  !!
2295  !!``This License'' refers to version 3 of the GNU General Public License.
2296  !!
2297  !!``Copyright'' also means copyright-like laws that apply to other kinds of
2298  !!works, such as semiconductor masks.
2299  !!
2300  !!``The Program'' refers to any copyrightable work licensed under this
2301  !!License. Each licensee is addressed as ``you''. ``Licensees'' and
2302  !!``recipients'' may be individuals or organizations.
2303  !!
2304  !!To ``modify'' a work means to copy from or adapt all or part of the work
2305  !!in a fashion requiring copyright permission, other than the making of an
2306  !!exact copy. The resulting work is called a ``modified version'' of the
2307  !!earlier work or a work ``based on'' the earlier work.
2308  !!
2309  !!A ``covered work'' means either the unmodified Program or a work based
2310  !!on the Program.
2311  !!
2312  !!To ``propagate'' a work means to do anything with it that, without
2313  !!permission, would make you directly or secondarily liable for
2314  !!infringement under applicable copyright law, except executing it on a
2315  !!computer or modifying a private copy. Propagation includes copying,
2316  !!distribution (with or without modification), making available to the
2317  !!public, and in some countries other activities as well.
2318  !!
2319  !!To ``convey'' a work means any kind of propagation that enables other
2320  !!parties to make or receive copies. Mere interaction with a user through
2321  !!a computer network, with no transfer of a copy, is not conveying.
2322  !!
2323  !!An interactive user interface displays ``Appropriate Legal Notices''
2324  !!to the extent that it includes a convenient and prominently visible
2325  !!feature that (1) displays an appropriate copyright notice, and (2)
2326  !!tells the user that there is no warranty for the work (except to the
2327  !!extent that warranties are provided), that licensees may convey the
2328  !!work under this License, and how to view a copy of this License. If
2329  !!the interface presents a list of user commands or options, such as a
2330  !!menu, a prominent item in the list meets this criterion.
2331  !!
2332  !!\item Source Code.
2333  !!
2334  !!The ``source code'' for a work means the preferred form of the work
2335  !!for making modifications to it. ``Object code'' means any non-source
2336  !!form of a work.
2337  !!
2338  !!A ``Standard Interface'' means an interface that either is an official
2339  !!standard defined by a recognized standards body, or, in the case of
2340  !!interfaces specified for a particular programming language, one that
2341  !!is widely used among developers working in that language.
2342  !!
2343  !!The ``System Libraries'' of an executable work include anything, other
2344  !!than the work as a whole, that (a) is included in the normal form of
2345  !!packaging a Major Component, but which is not part of that Major
2346  !!Component, and (b) serves only to enable use of the work with that
2347  !!Major Component, or to implement a Standard Interface for which an
2348  !!implementation is available to the public in source code form. A
2349  !!``Major Component'', in this context, means a major essential component
2350  !!(kernel, window system, and so on) of the specific operating system
2351  !!(if any) on which the executable work runs, or a compiler used to
2352  !!produce the work, or an object code interpreter used to run it.
2353  !!
2354  !!The ``Corresponding Source'' for a work in object code form means all
2355  !!the source code needed to generate, install, and (for an executable
2356  !!work) run the object code and to modify the work, including scripts to
2357  !!control those activities. However, it does not include the work's
2358  !!System Libraries, or general-purpose tools or generally available free
2359  !!programs which are used unmodified in performing those activities but
2360  !!which are not part of the work. For example, Corresponding Source
2361  !!includes interface definition files associated with source files for
2362  !!the work, and the source code for shared libraries and dynamically
2363  !!linked subprograms that the work is specifically designed to require,
2364  !!such as by intimate data communication or control flow between those
2365  !!subprograms and other parts of the work.
2366  !!
2367  !!The Corresponding Source need not include anything that users
2368  !!can regenerate automatically from other parts of the Corresponding
2369  !!Source.
2370  !!
2371  !!The Corresponding Source for a work in source code form is that
2372  !!same work.
2373  !!
2374  !!\item Basic Permissions.
2375  !!
2376  !!All rights granted under this License are granted for the term of
2377  !!copyright on the Program, and are irrevocable provided the stated
2378  !!conditions are met. This License explicitly affirms your unlimited
2379  !!permission to run the unmodified Program. The output from running a
2380  !!covered work is covered by this License only if the output, given its
2381  !!content, constitutes a covered work. This License acknowledges your
2382  !!rights of fair use or other equivalent, as provided by copyright law.
2383  !!
2384  !!You may make, run and propagate covered works that you do not
2385  !!convey, without conditions so long as your license otherwise remains
2386  !!in force. You may convey covered works to others for the sole purpose
2387  !!of having them make modifications exclusively for you, or provide you
2388  !!with facilities for running those works, provided that you comply with
2389  !!the terms of this License in conveying all material for which you do
2390  !!not control copyright. Those thus making or running the covered works
2391  !!for you must do so exclusively on your behalf, under your direction
2392  !!and control, on terms that prohibit them from making any copies of
2393  !!your copyrighted material outside their relationship with you.
2394  !!
2395  !!Conveying under any other circumstances is permitted solely under
2396  !!the conditions stated below. Sublicensing is not allowed; section 10
2397  !!makes it unnecessary.
2398  !!
2399  !!\item Protecting Users' Legal Rights From Anti-Circumvention Law.
2400  !!
2401  !!No covered work shall be deemed part of an effective technological
2402  !!measure under any applicable law fulfilling obligations under article
2403  !!11 of the WIPO copyright treaty adopted on 20 December 1996, or
2404  !!similar laws prohibiting or restricting circumvention of such
2405  !!measures.
2406  !!
2407  !!When you convey a covered work, you waive any legal power to forbid
2408  !!circumvention of technological measures to the extent such circumvention
2409  !!is effected by exercising rights under this License with respect to
2410  !!the covered work, and you disclaim any intention to limit operation or
2411  !!modification of the work as a means of enforcing, against the work's
2412  !!users, your or third parties' legal rights to forbid circumvention of
2413  !!technological measures.
2414  !!
2415  !!\item Conveying Verbatim Copies.
2416  !!
2417  !!You may convey verbatim copies of the Program's source code as you
2418  !!receive it, in any medium, provided that you conspicuously and
2419  !!appropriately publish on each copy an appropriate copyright notice;
2420  !!keep intact all notices stating that this License and any
2421  !!non-permissive terms added in accord with section 7 apply to the code;
2422  !!keep intact all notices of the absence of any warranty; and give all
2423  !!recipients a copy of this License along with the Program.
2424  !!
2425  !!You may charge any price or no price for each copy that you convey,
2426  !!and you may offer support or warranty protection for a fee.
2427  !!
2428  !!\item Conveying Modified Source Versions.
2429  !!
2430  !!You may convey a work based on the Program, or the modifications to
2431  !!produce it from the Program, in the form of source code under the
2432  !!terms of section 4, provided that you also meet all of these conditions:
2433  !! \begin{enumerate}
2434  !! \item The work must carry prominent notices stating that you modified
2435  !! it, and giving a relevant date.
2436  !!
2437  !! \item The work must carry prominent notices stating that it is
2438  !! released under this License and any conditions added under section
2439  !! 7. This requirement modifies the requirement in section 4 to
2440  !! ``keep intact all notices''.
2441  !!
2442  !! \item You must license the entire work, as a whole, under this
2443  !! License to anyone who comes into possession of a copy. This
2444  !! License will therefore apply, along with any applicable section 7
2445  !! additional terms, to the whole of the work, and all its parts,
2446  !! regardless of how they are packaged. This License gives no
2447  !! permission to license the work in any other way, but it does not
2448  !! invalidate such permission if you have separately received it.
2449  !!
2450  !! \item If the work has interactive user interfaces, each must display
2451  !! Appropriate Legal Notices; however, if the Program has interactive
2452  !! interfaces that do not display Appropriate Legal Notices, your
2453  !! work need not make them do so.
2454  !!\end{enumerate}
2455  !!A compilation of a covered work with other separate and independent
2456  !!works, which are not by their nature extensions of the covered work,
2457  !!and which are not combined with it such as to form a larger program,
2458  !!in or on a volume of a storage or distribution medium, is called an
2459  !!``aggregate'' if the compilation and its resulting copyright are not
2460  !!used to limit the access or legal rights of the compilation's users
2461  !!beyond what the individual works permit. Inclusion of a covered work
2462  !!in an aggregate does not cause this License to apply to the other
2463  !!parts of the aggregate.
2464  !!
2465  !!\item Conveying Non-Source Forms.
2466  !!
2467  !!You may convey a covered work in object code form under the terms
2468  !!of sections 4 and 5, provided that you also convey the
2469  !!machine-readable Corresponding Source under the terms of this License,
2470  !!in one of these ways:
2471  !! \begin{enumerate}
2472  !! \item Convey the object code in, or embodied in, a physical product
2473  !! (including a physical distribution medium), accompanied by the
2474  !! Corresponding Source fixed on a durable physical medium
2475  !! customarily used for software interchange.
2476  !!
2477  !! \item Convey the object code in, or embodied in, a physical product
2478  !! (including a physical distribution medium), accompanied by a
2479  !! written offer, valid for at least three years and valid for as
2480  !! long as you offer spare parts or customer support for that product
2481  !! model, to give anyone who possesses the object code either (1) a
2482  !! copy of the Corresponding Source for all the software in the
2483  !! product that is covered by this License, on a durable physical
2484  !! medium customarily used for software interchange, for a price no
2485  !! more than your reasonable cost of physically performing this
2486  !! conveying of source, or (2) access to copy the
2487  !! Corresponding Source from a network server at no charge.
2488  !!
2489  !! \item Convey individual copies of the object code with a copy of the
2490  !! written offer to provide the Corresponding Source. This
2491  !! alternative is allowed only occasionally and noncommercially, and
2492  !! only if you received the object code with such an offer, in accord
2493  !! with subsection 6b.
2494  !!
2495  !! \item Convey the object code by offering access from a designated
2496  !! place (gratis or for a charge), and offer equivalent access to the
2497  !! Corresponding Source in the same way through the same place at no
2498  !! further charge. You need not require recipients to copy the
2499  !! Corresponding Source along with the object code. If the place to
2500  !! copy the object code is a network server, the Corresponding Source
2501  !! may be on a different server (operated by you or a third party)
2502  !! that supports equivalent copying facilities, provided you maintain
2503  !! clear directions next to the object code saying where to find the
2504  !! Corresponding Source. Regardless of what server hosts the
2505  !! Corresponding Source, you remain obligated to ensure that it is
2506  !! available for as long as needed to satisfy these requirements.
2507  !!
2508  !! \item Convey the object code using peer-to-peer transmission, provided
2509  !! you inform other peers where the object code and Corresponding
2510  !! Source of the work are being offered to the general public at no
2511  !! charge under subsection 6d.
2512  !! \end{enumerate}
2513  !!
2514  !!A separable portion of the object code, whose source code is excluded
2515  !!from the Corresponding Source as a System Library, need not be
2516  !!included in conveying the object code work.
2517  !!
2518  !!A ``User Product'' is either (1) a ``consumer product'', which means any
2519  !!tangible personal property which is normally used for personal, family,
2520  !!or household purposes, or (2) anything designed or sold for incorporation
2521  !!into a dwelling. In determining whether a product is a consumer product,
2522  !!doubtful cases shall be resolved in favor of coverage. For a particular
2523  !!product received by a particular user, ``normally used'' refers to a
2524  !!typical or common use of that class of product, regardless of the status
2525  !!of the particular user or of the way in which the particular user
2526  !!actually uses, or expects or is expected to use, the product. A product
2527  !!is a consumer product regardless of whether the product has substantial
2528  !!commercial, industrial or non-consumer uses, unless such uses represent
2529  !!the only significant mode of use of the product.
2530  !!
2531  !!``Installation Information'' for a User Product means any methods,
2532  !!procedures, authorization keys, or other information required to install
2533  !!and execute modified versions of a covered work in that User Product from
2534  !!a modified version of its Corresponding Source. The information must
2535  !!suffice to ensure that the continued functioning of the modified object
2536  !!code is in no case prevented or interfered with solely because
2537  !!modification has been made.
2538  !!
2539  !!If you convey an object code work under this section in, or with, or
2540  !!specifically for use in, a User Product, and the conveying occurs as
2541  !!part of a transaction in which the right of possession and use of the
2542  !!User Product is transferred to the recipient in perpetuity or for a
2543  !!fixed term (regardless of how the transaction is characterized), the
2544  !!Corresponding Source conveyed under this section must be accompanied
2545  !!by the Installation Information. But this requirement does not apply
2546  !!if neither you nor any third party retains the ability to install
2547  !!modified object code on the User Product (for example, the work has
2548  !!been installed in ROM).
2549  !!
2550  !!The requirement to provide Installation Information does not include a
2551  !!requirement to continue to provide support service, warranty, or updates
2552  !!for a work that has been modified or installed by the recipient, or for
2553  !!the User Product in which it has been modified or installed. Access to a
2554  !!network may be denied when the modification itself materially and
2555  !!adversely affects the operation of the network or violates the rules and
2556  !!protocols for communication across the network.
2557  !!
2558  !!Corresponding Source conveyed, and Installation Information provided,
2559  !!in accord with this section must be in a format that is publicly
2560  !!documented (and with an implementation available to the public in
2561  !!source code form), and must require no special password or key for
2562  !!unpacking, reading or copying.
2563  !!
2564  !!\item Additional Terms.
2565  !!
2566  !!``Additional permissions'' are terms that supplement the terms of this
2567  !!License by making exceptions from one or more of its conditions.
2568  !!Additional permissions that are applicable to the entire Program shall
2569  !!be treated as though they were included in this License, to the extent
2570  !!that they are valid under applicable law. If additional permissions
2571  !!apply only to part of the Program, that part may be used separately
2572  !!under those permissions, but the entire Program remains governed by
2573  !!this License without regard to the additional permissions.
2574  !!
2575  !!When you convey a copy of a covered work, you may at your option
2576  !!remove any additional permissions from that copy, or from any part of
2577  !!it. (Additional permissions may be written to require their own
2578  !!removal in certain cases when you modify the work.) You may place
2579  !!additional permissions on material, added by you to a covered work,
2580  !!for which you have or can give appropriate copyright permission.
2581  !!
2582  !!Notwithstanding any other provision of this License, for material you
2583  !!add to a covered work, you may (if authorized by the copyright holders of
2584  !!that material) supplement the terms of this License with terms:
2585  !! \begin{enumerate}
2586  !! \item Disclaiming warranty or limiting liability differently from the
2587  !! terms of sections 15 and 16 of this License; or
2588  !!
2589  !! \item Requiring preservation of specified reasonable legal notices or
2590  !! author attributions in that material or in the Appropriate Legal
2591  !! Notices displayed by works containing it; or
2592  !!
2593  !! \item Prohibiting misrepresentation of the origin of that material, or
2594  !! requiring that modified versions of such material be marked in
2595  !! reasonable ways as different from the original version; or
2596  !!
2597  !! \item Limiting the use for publicity purposes of names of licensors or
2598  !! authors of the material; or
2599  !!
2600  !! \item Declining to grant rights under trademark law for use of some
2601  !! trade names, trademarks, or service marks; or
2602  !!
2603  !! \item Requiring indemnification of licensors and authors of that
2604  !! material by anyone who conveys the material (or modified versions of
2605  !! it) with contractual assumptions of liability to the recipient, for
2606  !! any liability that these contractual assumptions directly impose on
2607  !! those licensors and authors.
2608  !! \end{enumerate}
2609  !!
2610  !!All other non-permissive additional terms are considered ``further
2611  !!restrictions'' within the meaning of section 10. If the Program as you
2612  !!received it, or any part of it, contains a notice stating that it is
2613  !!governed by this License along with a term that is a further
2614  !!restriction, you may remove that term. If a license document contains
2615  !!a further restriction but permits relicensing or conveying under this
2616  !!License, you may add to a covered work material governed by the terms
2617  !!of that license document, provided that the further restriction does
2618  !!not survive such relicensing or conveying.
2619  !!
2620  !!If you add terms to a covered work in accord with this section, you
2621  !!must place, in the relevant source files, a statement of the
2622  !!additional terms that apply to those files, or a notice indicating
2623  !!where to find the applicable terms.
2624  !!
2625  !!Additional terms, permissive or non-permissive, may be stated in the
2626  !!form of a separately written license, or stated as exceptions;
2627  !!the above requirements apply either way.
2628  !!
2629  !!\item Termination.
2630  !!
2631  !!You may not propagate or modify a covered work except as expressly
2632  !!provided under this License. Any attempt otherwise to propagate or
2633  !!modify it is void, and will automatically terminate your rights under
2634  !!this License (including any patent licenses granted under the third
2635  !!paragraph of section 11).
2636  !!
2637  !!However, if you cease all violation of this License, then your
2638  !!license from a particular copyright holder is reinstated (a)
2639  !!provisionally, unless and until the copyright holder explicitly and
2640  !!finally terminates your license, and (b) permanently, if the copyright
2641  !!holder fails to notify you of the violation by some reasonable means
2642  !!prior to 60 days after the cessation.
2643  !!
2644  !!Moreover, your license from a particular copyright holder is
2645  !!reinstated permanently if the copyright holder notifies you of the
2646  !!violation by some reasonable means, this is the first time you have
2647  !!received notice of violation of this License (for any work) from that
2648  !!copyright holder, and you cure the violation prior to 30 days after
2649  !!your receipt of the notice.
2650  !!
2651  !!Termination of your rights under this section does not terminate the
2652  !!licenses of parties who have received copies or rights from you under
2653  !!this License. If your rights have been terminated and not permanently
2654  !!reinstated, you do not qualify to receive new licenses for the same
2655  !!material under section 10.
2656  !!
2657  !!\item Acceptance Not Required for Having Copies.
2658  !!
2659  !!You are not required to accept this License in order to receive or
2660  !!run a copy of the Program. Ancillary propagation of a covered work
2661  !!occurring solely as a consequence of using peer-to-peer transmission
2662  !!to receive a copy likewise does not require acceptance. However,
2663  !!nothing other than this License grants you permission to propagate or
2664  !!modify any covered work. These actions infringe copyright if you do
2665  !!not accept this License. Therefore, by modifying or propagating a
2666  !!covered work, you indicate your acceptance of this License to do so.
2667  !!
2668  !!\item Automatic Licensing of Downstream Recipients.
2669  !!
2670  !!Each time you convey a covered work, the recipient automatically
2671  !!receives a license from the original licensors, to run, modify and
2672  !!propagate that work, subject to this License. You are not responsible
2673  !!for enforcing compliance by third parties with this License.
2674  !!
2675  !!An ``entity transaction'' is a transaction transferring control of an
2676  !!organization, or substantially all assets of one, or subdividing an
2677  !!organization, or merging organizations. If propagation of a covered
2678  !!work results from an entity transaction, each party to that
2679  !!transaction who receives a copy of the work also receives whatever
2680  !!licenses to the work the party's predecessor in interest had or could
2681  !!give under the previous paragraph, plus a right to possession of the
2682  !!Corresponding Source of the work from the predecessor in interest, if
2683  !!the predecessor has it or can get it with reasonable efforts.
2684  !!
2685  !!You may not impose any further restrictions on the exercise of the
2686  !!rights granted or affirmed under this License. For example, you may
2687  !!not impose a license fee, royalty, or other charge for exercise of
2688  !!rights granted under this License, and you may not initiate litigation
2689  !!(including a cross-claim or counterclaim in a lawsuit) alleging that
2690  !!any patent claim is infringed by making, using, selling, offering for
2691  !!sale, or importing the Program or any portion of it.
2692  !!
2693  !!\item Patents.
2694  !!
2695  !!A ``contributor'' is a copyright holder who authorizes use under this
2696  !!License of the Program or a work on which the Program is based. The
2697  !!work thus licensed is called the contributor's ``contributor version''.
2698  !!
2699  !!A contributor's ``essential patent claims'' are all patent claims
2700  !!owned or controlled by the contributor, whether already acquired or
2701  !!hereafter acquired, that would be infringed by some manner, permitted
2702  !!by this License, of making, using, or selling its contributor version,
2703  !!but do not include claims that would be infringed only as a
2704  !!consequence of further modification of the contributor version. For
2705  !!purposes of this definition, ``control'' includes the right to grant
2706  !!patent sublicenses in a manner consistent with the requirements of
2707  !!this License.
2708  !!
2709  !!Each contributor grants you a non-exclusive, worldwide, royalty-free
2710  !!patent license under the contributor's essential patent claims, to
2711  !!make, use, sell, offer for sale, import and otherwise run, modify and
2712  !!propagate the contents of its contributor version.
2713  !!
2714  !!In the following three paragraphs, a ``patent license'' is any express
2715  !!agreement or commitment, however denominated, not to enforce a patent
2716  !!(such as an express permission to practice a patent or covenant not to
2717  !!sue for patent infringement). To ``grant'' such a patent license to a
2718  !!party means to make such an agreement or commitment not to enforce a
2719  !!patent against the party.
2720  !!
2721  !!If you convey a covered work, knowingly relying on a patent license,
2722  !!and the Corresponding Source of the work is not available for anyone
2723  !!to copy, free of charge and under the terms of this License, through a
2724  !!publicly available network server or other readily accessible means,
2725  !!then you must either (1) cause the Corresponding Source to be so
2726  !!available, or (2) arrange to deprive yourself of the benefit of the
2727  !!patent license for this particular work, or (3) arrange, in a manner
2728  !!consistent with the requirements of this License, to extend the patent
2729  !!license to downstream recipients. ``Knowingly relying'' means you have
2730  !!actual knowledge that, but for the patent license, your conveying the
2731  !!covered work in a country, or your recipient's use of the covered work
2732  !!in a country, would infringe one or more identifiable patents in that
2733  !!country that you have reason to believe are valid.
2734  !!
2735  !!If, pursuant to or in connection with a single transaction or
2736  !!arrangement, you convey, or propagate by procuring conveyance of, a
2737  !!covered work, and grant a patent license to some of the parties
2738  !!receiving the covered work authorizing them to use, propagate, modify
2739  !!or convey a specific copy of the covered work, then the patent license
2740  !!you grant is automatically extended to all recipients of the covered
2741  !!work and works based on it.
2742  !!
2743  !!A patent license is ``discriminatory'' if it does not include within
2744  !!the scope of its coverage, prohibits the exercise of, or is
2745  !!conditioned on the non-exercise of one or more of the rights that are
2746  !!specifically granted under this License. You may not convey a covered
2747  !!work if you are a party to an arrangement with a third party that is
2748  !!in the business of distributing software, under which you make payment
2749  !!to the third party based on the extent of your activity of conveying
2750  !!the work, and under which the third party grants, to any of the
2751  !!parties who would receive the covered work from you, a discriminatory
2752  !!patent license (a) in connection with copies of the covered work
2753  !!conveyed by you (or copies made from those copies), or (b) primarily
2754  !!for and in connection with specific products or compilations that
2755  !!contain the covered work, unless you entered into that arrangement,
2756  !!or that patent license was granted, prior to 28 March 2007.
2757  !!
2758  !!Nothing in this License shall be construed as excluding or limiting
2759  !!any implied license or other defenses to infringement that may
2760  !!otherwise be available to you under applicable patent law.
2761  !!
2762  !!\item No Surrender of Others' Freedom.
2763  !!
2764  !!If conditions are imposed on you (whether by court order, agreement or
2765  !!otherwise) that contradict the conditions of this License, they do not
2766  !!excuse you from the conditions of this License. If you cannot convey a
2767  !!covered work so as to satisfy simultaneously your obligations under this
2768  !!License and any other pertinent obligations, then as a consequence you may
2769  !!not convey it at all. For example, if you agree to terms that obligate you
2770  !!to collect a royalty for further conveying from those to whom you convey
2771  !!the Program, the only way you could satisfy both those terms and this
2772  !!License would be to refrain entirely from conveying the Program.
2773  !!
2774  !!\item Use with the GNU Affero General Public License.
2775  !!
2776  !!Notwithstanding any other provision of this License, you have
2777  !!permission to link or combine any covered work with a work licensed
2778  !!under version 3 of the GNU Affero General Public License into a single
2779  !!combined work, and to convey the resulting work. The terms of this
2780  !!License will continue to apply to the part which is the covered work,
2781  !!but the special requirements of the GNU Affero General Public License,
2782  !!section 13, concerning interaction through a network will apply to the
2783  !!combination as such.
2784  !!
2785  !!\item Revised Versions of this License.
2786  !!
2787  !!The Free Software Foundation may publish revised and/or new versions of
2788  !!the GNU General Public License from time to time. Such new versions will
2789  !!be similar in spirit to the present version, but may differ in detail to
2790  !!address new problems or concerns.
2791  !!
2792  !!Each version is given a distinguishing version number. If the
2793  !!Program specifies that a certain numbered version of the GNU General
2794  !!Public License ``or any later version'' applies to it, you have the
2795  !!option of following the terms and conditions either of that numbered
2796  !!version or of any later version published by the Free Software
2797  !!Foundation. If the Program does not specify a version number of the
2798  !!GNU General Public License, you may choose any version ever published
2799  !!by the Free Software Foundation.
2800  !!
2801  !!If the Program specifies that a proxy can decide which future
2802  !!versions of the GNU General Public License can be used, that proxy's
2803  !!public statement of acceptance of a version permanently authorizes you
2804  !!to choose that version for the Program.
2805  !!
2806  !!Later license versions may give you additional or different
2807  !!permissions. However, no additional obligations are imposed on any
2808  !!author or copyright holder as a result of your choosing to follow a
2809  !!later version.
2810  !!
2811  !!\item Disclaimer of Warranty.
2812  !!
2813  !!\begin{sloppypar}
2814  !! THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY
2815  !! APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE
2816  !! COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM ``AS IS''
2817  !! WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED,
2818  !! INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
2819  !! MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE
2820  !! RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU.
2821  !! SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL
2822  !! NECESSARY SERVICING, REPAIR OR CORRECTION.
2823  !!\end{sloppypar}
2824  !!
2825  !!\item Limitation of Liability.
2826  !!
2827  !! IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN
2828  !! WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MODIFIES
2829  !! AND/OR CONVEYS THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR
2830  !! DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL
2831  !! DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM
2832  !! (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED
2833  !! INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE
2834  !! OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH
2835  !! HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH
2836  !! DAMAGES.
2837  !!
2838  !!\item Interpretation of Sections 15 and 16.
2839  !!
2840  !!If the disclaimer of warranty and limitation of liability provided
2841  !!above cannot be given local legal effect according to their terms,
2842  !!reviewing courts shall apply local law that most closely approximates
2843  !!an absolute waiver of all civil liability in connection with the
2844  !!Program, unless a warranty or assumption of liability accompanies a
2845  !!copy of the Program in return for a fee.
2846  !!
2847  !!\begin{center}
2848  !!{\Large\sc End of Terms and Conditions}
2849  !!
2850  !!\bigskip
2851  !!How to Apply These Terms to Your New Programs
2852  !!\end{center}
2853  !!
2854  !!If you develop a new program, and you want it to be of the greatest
2855  !!possible use to the public, the best way to achieve this is to make it
2856  !!free software which everyone can redistribute and change under these terms.
2857  !!
2858  !!To do so, attach the following notices to the program. It is safest
2859  !!to attach them to the start of each source file to most effectively
2860  !!state the exclusion of warranty; and each file should have at least
2861  !!the ``copyright'' line and a pointer to where the full notice is found.
2862  !!
2863  !!{\footnotesize
2864  !!\begin{verbatim}
2865  !!<one line to give the program's name and a brief idea of what it does.>
2866  !!
2867  !!Copyright (C) <textyear> <name of author>
2868  !!
2869  !!This program is free software: you can redistribute it and/or modify
2870  !!it under the terms of the GNU General Public License as published by
2871  !!the Free Software Foundation, either version 3 of the License, or
2872  !!(at your option) any later version.
2873  !!
2874  !!This program is distributed in the hope that it will be useful,
2875  !!but WITHOUT ANY WARRANTY; without even the implied warranty of
2876  !!MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
2877  !!GNU General Public License for more details.
2878  !!
2879  !!You should have received a copy of the GNU General Public License
2880  !!along with this program. If not, see <http://www.gnu.org/licenses/>.
2881  !!\end{verbatim}
2882  !!}
2883  !!
2884  !!Also add information on how to contact you by electronic and paper mail.
2885  !!
2886  !!If the program does terminal interaction, make it output a short
2887  !!notice like this when it starts in an interactive mode:
2888  !!
2889  !!{\footnotesize
2890  !!\begin{verbatim}
2891  !!<program> Copyright (C) <year> <name of author>
2892  !!
2893  !!This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
2894  !!This is free software, and you are welcome to redistribute it
2895  !!under certain conditions; type `show c' for details.
2896  !!\end{verbatim}
2897  !!}
2898  !!
2899  !!The hypothetical commands {\tt show w} and {\tt show c} should show
2900  !!the appropriate
2901  !!parts of the General Public License. Of course, your program's commands
2902  !!might be different; for a GUI interface, you would use an ``about box''.
2903  !!
2904  !!You should also get your employer (if you work as a programmer) or
2905  !!school, if any, to sign a ``copyright disclaimer'' for the program, if
2906  !!necessary. For more information on this, and how to apply and follow
2907  !!the GNU GPL, see \texttt{http://www.gnu.org/licenses/}.
2908  !!
2909  !!The GNU General Public License does not permit incorporating your
2910  !!program into proprietary programs. If your program is a subroutine
2911  !!library, you may consider it more useful to permit linking proprietary
2912  !!applications with the library. If this is what you want to do, use
2913  !!the GNU Lesser General Public License instead of this License. But
2914  !!first, please read \newline\texttt{http://www.gnu.org/philosophy/why-not-lgpl.html}.
2915  !!
2916  !!\end{enumerate}
2917 
2918  !(doc)footer
character(5), parameter, public fi8p
Definition: lib_vtk_io.F:98
integer(i4p) function vtk_var_vect_r4(VEC_TYPE, NC_NN, VARNAME, VARX, VARY, VARZ)
Definition: lib_vtk_io.F:1476
integer(i4p) function vtk_var_scal_r8(NC_NN, VARNAME, VAR)
Definition: lib_vtk_io.F:1324
character(len=len(string)) function upper_case(STRING)
Definition: lib_vtk_io.F:165
integer, parameter, public i_p
Definition: lib_vtk_io.F:85
character(5), parameter, public fi_p
Definition: lib_vtk_io.F:102
integer(i4p) function vtk_geo_strp_r8(NX, NY, NZ, X0, Y0, Z0, DX, DY, DZ)
Definition: lib_vtk_io.F:520
integer(i4p) function vtk_geo_rect_r4(NX, NY, NZ, X, Y, Z)
Definition: lib_vtk_io.F:776
integer(i4p) function, public vtk_dat(NC_NN, VAR_LOCATION)
Definition: lib_vtk_io.F:1043
integer, parameter, public i2p
Definition: lib_vtk_io.F:83
Y.AUDOUIN 30/06/2013 V6P3
Definition: lib_vtk_io.F:44
integer(i4p) f_out
Definition: lib_vtk_io.F:111
integer, parameter, public r_p
Definition: lib_vtk_io.F:78
integer(i4p) function vtk_var_text_r8(NC_NN, DIMM, VARNAME, TEXTCOO)
Definition: lib_vtk_io.F:1561
integer(i4p) function vtk_var_text_r4(NC_NN, DIMM, VARNAME, TEXTCOO)
Definition: lib_vtk_io.F:1606
integer(i4p) function vtk_geo_strp_r4(NX, NY, NZ, X0, Y0, Z0, DX, DY, DZ)
Definition: lib_vtk_io.F:569
integer(i4p) function vtk_geo_strg_r4(NX, NY, NZ, NN, X, Y, Z)
Definition: lib_vtk_io.F:663
integer(i4p) function vtk_var_vect_r8(VEC_TYPE, NC_NN, VARNAME, VARX, VARY, VARZ)
Definition: lib_vtk_io.F:1427
character(10), parameter, public fr_p
Definition: lib_vtk_io.F:95
integer(i4p) function vtk_geo_unst_r8(NN, X, Y, Z)
Definition: lib_vtk_io.F:843
integer(i4p) function getunit()
Definition: lib_vtk_io.F:125
character(4), parameter, public fi2p
Definition: lib_vtk_io.F:100
character(5), parameter, public fi4p
Definition: lib_vtk_io.F:99
integer(i4p) function, public vtk_end()
Definition: lib_vtk_io.F:1651
integer(i4p), parameter maxlen
Definition: lib_vtk_io.F:107
integer, parameter, public r8p
Definition: lib_vtk_io.F:76
integer, parameter, public r4p
Definition: lib_vtk_io.F:77
integer(i4p) function vtk_geo_unst_r4(NN, X, Y, Z)
Definition: lib_vtk_io.F:880
integer(i4p) function vtk_var_scal_r4(NC_NN, VARNAME, VAR)
Definition: lib_vtk_io.F:1358
character(10), parameter, public fr16p
Definition: lib_vtk_io.F:92
integer(i4p), parameter f_out_ascii
Definition: lib_vtk_io.F:109
integer(i4p) function, public vtk_con(NC, CONNECT, CELL_TYPE)
Definition: lib_vtk_io.F:918
integer, parameter, public i8p
Definition: lib_vtk_io.F:81
integer(i4p) function, public vtk_ini(OUTPUT_FORMAT, FILENAME, TITLE, MESH_TOPOLOGY)
Definition: lib_vtk_io.F:205
integer, parameter, public i1p
Definition: lib_vtk_io.F:84
character(10), parameter, public fr8p
Definition: lib_vtk_io.F:93
integer, parameter, public i4p
Definition: lib_vtk_io.F:82
character(4), parameter, public fi1p
Definition: lib_vtk_io.F:101
integer(i4p) unit_vtk
Definition: lib_vtk_io.F:113
integer(i4p), parameter f_out_binary
Definition: lib_vtk_io.F:110
integer(i4p) function vtk_var_vect_i4(NC_NN, VARNAME, VARX, VARY, VARZ)
Definition: lib_vtk_io.F:1525
integer(i4p) function vtk_var_scal_i4(NC_NN, VARNAME, VAR)
Definition: lib_vtk_io.F:1392
character(len=maxlen) topology
Definition: lib_vtk_io.F:112
character(1), parameter end_rec
Definition: lib_vtk_io.F:108
character(9), parameter, public fr4p
Definition: lib_vtk_io.F:94
integer, parameter, public r16p
Definition: lib_vtk_io.F:75
integer(i4p) function vtk_geo_rect_r8(NX, NY, NZ, X, Y, Z)
Definition: lib_vtk_io.F:709
integer(i4p) function vtk_geo_strg_r8(NX, NY, NZ, NN, X, Y, Z)
Definition: lib_vtk_io.F:617