Forward compatibility: flex
[foam-extend-3.2.git] / applications / utilities / postProcessing / dataConversion / foamToTecplot360 / tecio / examples / comtest / comtest.f90
blobe4ea709827ce82fa06ff06e8a8e2956a86c8e7fd
2 ! Complex example FORTRAN program to write a
3 ! binary data file for Tecplot. This example
4 ! does the following:
6 ! 1. Open a data file called "field.plt."
7 ! 2. Open a data file called "line.plt."
8 ! 3. Assign values for X, Y and P. These will be used
9 ! in both the ordered and FE data files.
10 ! 4. Write out an ordered zone dimensioned 4 x 5 to "field.plt."
11 ! 5. Assign values for XL and YL arrays.
12 ! 6. Write out data for line plot to "line.plt." Make the data
13 ! use double precision.
14 ! 7. Write out a finite element zone to "field.plt."
15 ! 8. Write out a text record to "field.plt."
16 ! 9. Write out a geometry (circle) record to "field.plt."
17 ! 10. Close file 1.
18 ! 11. Close file 2.
20 Program ComplexTest
22 Include "tecio.f90"
24 REAL*4 X(4,5), Y(4,5), P(4,5)
25 REAL*8 XL(50), YL(50)
26 REAL*4 XLDummy(1), YLDummy(1)
27 EQUIVALENCE (XLDummy(1), XL(1))
28 EQUIVALENCE (YLDummy(1), YL(1))
29 REAL*8 SolTime
30 INTEGER*4 Debug,I,J,K,L,III,NPts,NElm,DIsDouble,VIsDouble,FileType
31 INTEGER*4 IMax,JMax,KMax,NM(4,12)
32 INTEGER*4 StrandID,ParentZn
33 INTEGER*4 SharingZone(3)
34 REAL*8 XP, YP, ZP, FH, LineSpacing, PatternLength
35 REAL*8 BoxMargin, BoxLineThickness, TextAngle
36 INTEGER*4 AttachToZone, Zone, Scope, PositionCoordSys
37 INTEGER*4 Clipping
38 INTEGER*4 FontType, HeightUnits, Anchor, BoxType
39 INTEGER*4 IsFilled, GeomType, LinePattern, NumEllipsePts
40 INTEGER*4 BoxColor, BoxFillColor, TextColor, Color, FillColor
41 INTEGER*4 ArrowheadStyle, ArrowheadAttachment, NumSegments
42 INTEGER*4 NumSegPts(1)
43 REAL*8 LineThickness, ArrowheadSize, ArrowheadAngle
44 REAL*4 XGeomData(1), YGeomData(1), ZGeomData(1)
45 CHARACTER*1 NULCHAR
46 INTEGER*4 Zero
47 POINTER (NullPtr,Null)
48 INTEGER*4 Null(*)
50 Debug = 2
51 VIsDouble = 0
52 FileType = 0
53 DIsDouble = 0
54 NULCHAR = CHAR(0)
55 Zero = 0
56 NullPtr = 0
58 ! Open field.plt and write the header information.
60 I = TECINI112('DATASET WITH 1 ORDERED ZONE, '// &
61 '1 QUAD ZONE OVER 2 TIME STEPS'//NULCHAR, &
62 'X Y P'//NULCHAR, &
63 'field.plt'//NULCHAR, &
64 '.'//NULCHAR, &
65 FileType, &
66 Debug, &
67 VIsDouble)
69 ! Open line.plt and write the header information.
71 VIsDouble = 1
72 I = TECINI112('DATASET WITH ONE I-ORDERED ZONE'//NULCHAR, &
73 'X Y'//NULCHAR, &
74 'line.plt'//NULCHAR, &
75 '.'//NULCHAR, &
76 FileType, &
77 Debug, &
78 VIsDouble)
81 ! Calculate values for the field variables.
83 Do 10 J = 1,5
84 Do 10 I = 1,4
85 X(I,J) = I
86 Y(I,J) = J
87 P(I,J) = I*J
88 10 Continue
91 ! Make sure writing to file #1.
93 III = 1
94 I = TECFIL112(III)
97 ! Write the zone header information for the ordered zone.
99 IMax = 4
100 JMax = 5
101 KMax = 1
102 SolTime = 10.0
103 StrandID = 1
104 ParentZn = 0
105 I = TECZNE112('Ordered Zone 1'//NULCHAR, &
106 0, & ! ZONETYPE
107 IMax, &
108 JMax, &
109 KMax, &
110 0, &
111 0, &
112 0, &
113 SolTime, &
114 StrandID, &
115 ParentZn, &
116 1, & ! ISBLOCK
117 0, & ! NumFaceConnections
118 0, & ! FaceNeighborMode
119 0, & ! TotalNumFaceNodes
120 0, & ! NumConnectedBoundaryFaces
121 0, & ! TotalNumBoundaryConnections
122 Null, & ! PassiveVarList
123 Null, & ! ValueLocation
124 Null, & ! ShareVarFromZone
125 0) ! ShareConnectivityFromZone)
128 ! Write out the field data for the ordered zone.
130 III = IMax*JMax
131 I = TECDAT112(III,X,DIsDouble)
132 I = TECDAT112(III,Y,DIsDouble)
133 I = TECDAT112(III,P,DIsDouble)
136 ! Calculate values for the I-ordered zone.
139 Do 20 I = 1,50
140 XL(I) = I
141 YL(I) = sin(I/20.0)
142 20 Continue
144 ! Switch to the 'line.plt' file (file number 2)
145 ! and write out the line plot data.
147 III = 2
148 I = TECFIL112(III)
150 ! Write the zone header information for the XY-data.
152 IMax = 50
153 JMax = 1
154 KMax = 1
155 SolTime = 0.0
156 StrandID = 0
157 I = TECZNE112('XY Line plot'//NULCHAR, &
158 0, &
159 IMax, &
160 JMax, &
161 KMax, &
162 0, &
163 0, &
164 0, &
165 SolTime, &
166 StrandID, &
167 ParentZn, &
168 1, &
169 0, &
170 0, &
171 0, &
172 0, &
173 0, &
174 Null, &
175 Null, &
176 Null, &
179 ! Write out the line plot.
181 DIsDouble = 1
182 III = IMax
183 I = TECDAT112(III,XLDummy,DIsDouble)
184 I = TECDAT112(III,YLDummy,DIsDouble)
187 ! Switch back to the field plot file and write out
188 ! the finite-element zone.
190 III = 1
191 I = TECFIL112(III)
193 ! Move the coordinates so this zone's not on top of the other
195 Do 30 J = 1,5
196 Do 30 I = 1,4
197 X(I,J) = I+5
198 Y(I,J) = J
199 P(I,J) = I*J
200 30 Continue
202 ! Write the zone header information for the finite-element zone.
204 NPts = 20
205 NElm = 12
206 KMax = 1
207 SolTime = 10.0
208 StrandID = 2
209 I = TECZNE112('Finite Zone 1'//NULCHAR, &
210 3, & ! FEQUADRILATERAL
211 NPts, &
212 NElm, &
213 KMax, &
214 0, &
215 0, &
216 0, &
217 SolTime, &
218 StrandID, &
219 ParentZn, &
220 1, &
221 0, &
222 0, &
223 0, &
224 0, &
225 0, &
226 Null, &
227 Null, &
228 Null, &
231 ! Write out the field data for the finite-element zone.
233 IMax = 4
234 JMax = 5
235 III = IMax*JMax
236 DIsDouble = 0
237 I = TECDAT112(III,X,DIsDouble)
238 I = TECDAT112(III,Y,DIsDouble)
239 I = TECDAT112(III,P,DIsDouble)
242 ! Calculate and then write out the connectivity list.
243 ! Note: The NM array references cells starting with
244 ! offset of 1.
247 Do 40 I = 1,IMax-1
248 Do 40 J = 1,JMax-1
249 K = I+(J-1)*(IMax-1)
250 L = I+(J-1)*IMax
251 NM(1,K) = L
252 NM(2,K) = L+1
253 NM(3,K) = L+IMax+1
254 NM(4,K) = L+IMax
255 40 Continue
257 I = TECNOD112(NM)
259 ! Calculate vlues for the new solution variable.
261 Do 50 J = 1,5
262 Do 50 I = 1,4
263 P(I,J) = 2*I*J
264 50 Continue
266 ! Write the zone header information for time step 2
268 IMax = 4
269 JMax = 5
270 KMax = 1
271 SolTime = 20.0
272 StrandID = 1
273 SharingZone(1) = 1
274 SharingZone(2) = 1
275 SharingZone(3) = 0
276 I = TECZNE112('Ordered Zone 2'//NULCHAR, &
277 0, & ! ORDERED
278 IMax, &
279 JMax, &
280 KMax, &
281 0, &
282 0, &
283 0, &
284 SolTime, &
285 StrandID, &
286 ParentZn, &
287 1, &
288 0, &
289 0, &
290 0, &
291 0, &
292 0, &
293 Null, &
294 Null, &
295 SharingZone, &
298 ! Write out the solution variable the grid variables are shared.
300 IMax = 4
301 JMax = 5
302 III = IMax*JMax
303 DIsDouble = 0
304 I = TECDAT112(III,P,DIsDouble)
306 ! Calculate values for the new solution variable.
308 Do 60 J = 1,5
309 Do 60 I = 1,4
310 P(I,J) = 3*I*J
311 60 Continue
313 ! Write another time step for the FEZone and share from the first
315 SolTime = 20.0
316 StrandID = 2
317 KMax = 0
318 SharingZone(1) = 2
319 SharingZone(2) = 2
320 SharingZone(3) = 0
321 I = TECZNE112('Finite Zone 2'//NULCHAR, &
322 3, & ! FEQUADRILATERAL
323 NPts, &
324 NElm, &
325 KMax, &
326 0, &
327 0, &
328 0, &
329 SolTime, &
330 StrandID, &
331 ParentZn, &
332 1, &
333 0, &
334 0, &
335 0, &
336 0, &
337 0, &
338 Null, &
339 Null, &
340 SharingZone, &
343 ! Write out the solution variable the grid variables are shared.
345 IMax = 4
346 JMax = 5
347 III = IMax*JMax
348 DIsDouble = 0
349 I = TECDAT112(III,P,DIsDouble)
352 ! Prepare to write out text record. Text is positioned
353 ! at 50, 50 in frame units and has a height 5 frame units.
355 XP = 50
356 YP = 50
357 FH = 5
358 Scope = 1
359 Clipping = 0
360 PositionCoordSys = 1
361 FontType = 1
362 HeightUnits = 1
363 AttachToZone = 0
364 Zone = 0
365 BoxType = 0
366 BoxMargin = 5.0
367 BoxLineThickness = 0.5
368 BoxColor = 3
369 BoxFillColor = 7
370 TextAngle = 0.0
371 Anchor = 0
372 LineSpacing = 1.5
373 TextColor = 0
375 III = TECTXT112(XP, &
376 YP, &
377 0.0d0, &
378 PositionCoordSys, &
379 AttachToZone, &
380 Zone, &
381 FontType, &
382 HeightUnits, &
383 FH, &
384 BoxType, &
385 BoxMargin, &
386 BoxLineThickness, &
387 BoxColor, &
388 BoxFillColor, &
389 TextAngle, &
390 Anchor, &
391 LineSpacing, &
392 TextColor, &
393 Scope, &
394 Clipping, &
395 'Hi Mom'//NULCHAR, &
396 NULCHAR)
399 ! Prepare to write out geometry record (circle). Circle is
400 ! positioned at 25, 25 in frame units and has a radius of 30.
401 ! Circle is drawn using a dashed line pattern.
405 XP = 25
406 YP = 25
407 ZP = 0.0
408 IsFilled = 0
409 Color = 0
410 FillColor = 7
411 GeomType = 2
412 LinePattern = 1
413 LineThickness = 0.3
414 PatternLength = 1
415 NumEllipsePts = 72
416 ArrowheadStyle = 0
417 ArrowheadAttachment = 0
418 ArrowheadSize = 0.0
419 ArrowheadAngle = 15.0
420 NumSegments = 1
421 NumSegPts(1) = 1
423 XGeomData(1) = 30
424 YGeomData(1) = 0.0
425 ZGeomData(1) = 0.0
428 III = TECGEO112(XP, &
429 YP, &
430 ZP, &
431 PositionCoordSys, &
432 AttachToZone, &
433 Zone, &
434 Color, &
435 FillColor, &
436 IsFilled, &
437 GeomType, &
438 LinePattern, &
439 PatternLength, &
440 LineThickness, &
441 NumEllipsePts, &
442 ArrowheadStyle, &
443 ArrowheadAttachment, &
444 ArrowheadSize, &
445 ArrowheadAngle, &
446 Scope, &
447 Clipping, &
448 NumSegments, &
449 NumSegPts, &
450 XGeomData, &
451 YGeomData, &
452 ZGeomData, &
453 NULCHAR)
456 ! Close out file 1.
458 I = TECEND112()
461 ! Close out file 2.
463 III = 2
464 I = TECFIL112(III)
465 I = TECEND112()
466 STOP