2 ! Complex example FORTRAN program to write a
3 ! binary data file for Tecplot. This example
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."
24 REAL*4 X(4,5), Y(4,5), P(4,5)
26 REAL*4 XLDummy(1), YLDummy(1)
27 EQUIVALENCE (XLDummy(1), XL(1))
28 EQUIVALENCE (YLDummy(1), YL(1))
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
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)
47 POINTER (NullPtr
,Null
)
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
, &
63 'field.plt'//NULCHAR
, &
69 ! Open line.plt and write the header information.
72 I
= TECINI112('DATASET WITH ONE I-ORDERED ZONE'//NULCHAR
, &
74 'line.plt'//NULCHAR
, &
81 ! Calculate values for the field variables.
91 ! Make sure writing to file #1.
97 ! Write the zone header information for the ordered zone.
105 I
= TECZNE112('Ordered Zone 1'//NULCHAR
, &
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.
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.
144 ! Switch to the 'line.plt' file (file number 2)
145 ! and write out the line plot data.
150 ! Write the zone header information for the XY-data.
157 I
= TECZNE112('XY Line plot'//NULCHAR
, &
179 ! Write out the line plot.
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.
193 ! Move the coordinates so this zone's not on top of the other
202 ! Write the zone header information for the finite-element zone.
209 I
= TECZNE112('Finite Zone 1'//NULCHAR
, &
210 3, & ! FEQUADRILATERAL
231 ! Write out the field data for the finite-element zone.
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
259 ! Calculate vlues for the new solution variable.
266 ! Write the zone header information for time step 2
276 I
= TECZNE112('Ordered Zone 2'//NULCHAR
, &
298 ! Write out the solution variable the grid variables are shared.
304 I
= TECDAT112(III
,P
,DIsDouble
)
306 ! Calculate values for the new solution variable.
313 ! Write another time step for the FEZone and share from the first
321 I
= TECZNE112('Finite Zone 2'//NULCHAR
, &
322 3, & ! FEQUADRILATERAL
343 ! Write out the solution variable the grid variables are shared.
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.
367 BoxLineThickness
= 0.5
375 III
= TECTXT112(XP
, &
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.
417 ArrowheadAttachment
= 0
419 ArrowheadAngle
= 15.0
428 III
= TECGEO112(XP
, &
443 ArrowheadAttachment
, &