CFD Online Logo CFD Online URL
www.cfd-online.com
[Sponsors]
Home > Forums > Visualization & Post-Processing Software > Tecplot

I created a tecplot binary file...

Register Blogs Community New Posts Updated Threads Search

Like Tree5Likes
  • 5 Post By wenlong

Reply
 
LinkBack Thread Tools Search this Thread Display Modes
Old   January 7, 2012, 19:57
Default I created a tecplot binary file...
  #1
New Member
 
Lupo Ci
Join Date: Aug 2010
Posts: 16
Rep Power: 15
Lupocci is on a distinguished road
Dear all, I wrote a fortran code to create a binary .plt file containing a triangular mesh and relevant results for each nodes that can be read from tecplot. I read the manual http://download.tecplot.com/360/dataformat.pdf here and I followed the instruction in appendix A (pag 147). I really cannot understand what s wrong with my code. Tecplot reads the file but the mesh is wrong. I checked everything plenty of times, everything looks fine to me. Did anybody do that?any tecplot expert that can tell me what is wrong with my code? I paste the code below. In my code nodi contains the number of nodes and maglie contains the number of cells. i am simply trying to obtain the triangular mesh made of 4 elements in figure 4.10 pag 130.
thanks

Code:
        Program tecplot

          IMPLICIT NONE
    INTEGER nodi,maglie,ncan,j,iter,i, buttaINT,iWRITE,nTIMEstep,
     & iREAD,MAXexten,posiz,nOUT,k,N1,N2,N3,kkk,M,nodiGEO,jSTAMPA,
     & NumVar,FileType,ZoneType,StrandID,VarLoc,
     & jmax
    REAL*4 dt,BUTTA,butta1,butta2,butta4,butta3,butta5
      real*8 t,DBLEmin,DBLEmax
      integer, ALLOCATABLE :: iterOUT(:),n123(:,:),nodeCELLcenter(:)
      real*4, ALLOCATABLE :: vettore(:),tOUT(:),x(:),CSprint(:,:),
     &  y(:),z(:),CSnod(:),CS(:,:),area(:),areaNOD(:)
    character*40 nomefile,FM,variab,NOMEFILEGEO,intNAME,fileBUTTA
      character*8 header
      character*1 aster
      CHARACTER*1 NULCHAR
      logical stampa


        nodi   = 6
      maglie = 4
      x(1)=-1.0; y(1)= 0.0  
      x(2)= 0.0; y(2)= 0.0  
      x(3)= 1.0; y(3)= 0.0  
      x(4)=-0.5; y(4)= 0.8  
      x(5)= 0.5; y(5)= 0.8  
      x(6)= 0.0; y(6)= 1.6  
   numvar = 2
      allocate (CSprint(max(maglie,nodi),numvar),nodeCELLcenter(numvar))
  !       
      ! write BINARY FILE FOR TECPLOT
      !
      ! All character strings are null terminated (i.e. terminated by a zero value)
         !header = '#!TDV112'
         iwrite = iwrite+1
         write(36,rec=iwrite) '#!TDV112' !header
         iwrite = iwrite+2 !2 because it is a  char*8 and it fills 8 byte (2*recl)
         
          !ii. Integer value of 1.
          buttaINT =1
          write(36,rec=iwrite) buttaINT  ; iwrite = iwrite+1
          
          
          !iii. Title and variable names.
          FileType = 0 !Title and variable names. 0 = FULL,1 = GRID, 2 = SOLUTION
          write(36,rec=iwrite) FileType ; iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR('T') ; iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR(NULCHAR) ; iwrite = iwrite+1
!
          write(36,rec=iwrite) NumVar  ; iwrite = iwrite+1
          !DO I=1,NUMVAR
          !!Variable names (INT32*N). N = L[1] + L[2] + ....  L[NumVar]where:L[i] = length of the ith variable name + 1(for the  terminating 0 value).
            write(36,rec=iwrite) ICHAR('x') 
            iwrite = iwrite+1
            write(36,rec=iwrite) ICHAR(NULCHAR)
            iwrite = iwrite+1
            write(36,rec=iwrite) ICHAR('y') 
            iwrite = iwrite+1
            write(36,rec=iwrite) ICHAR(NULCHAR)
            iwrite = iwrite+1
          !ENDDO
          !iv. Zones
          BUTTA = 299.0 !Zone marker.
          write(36,rec=iwrite) BUTTA      ;iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR('Z') ;iwrite = iwrite+1 !Zone name  (INT32*N). N = (length of zone name) + 1(for the terminating 0 value).
          write(36,rec=iwrite) ICHAR('O') ;iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR('N') ;iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR('E') ;iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR('1') ;iwrite = iwrite+1
          write(36,rec=iwrite) ICHAR(NULCHAR) ; iwrite = iwrite+1
          write(36,rec=iwrite) -1 !0 !ParentZone: 0 = indicates that  this zone is not associated with a parent zone.>0 = A value greater  than zero is considered this zone's parent. 
          iwrite = iwrite+1
          StrandID = 0
          write(36,rec=iwrite) StrandID !IN REALTA IL MANUALE DICE  StrandID=0 =>static zone  StrandID: -2 = pending strand ID for  assignmentby Tecplot; -1 = static strand ID; 0 <= N < 32700 valid  strand ID
          iwrite = iwrite+1
          t =t + DBLE(dt)
          write(36,rec=iwrite) t
          iwrite = iwrite+1
          iwrite = iwrite+1
          write(36,rec=iwrite) -1 !Not used.
          iwrite = iwrite+1
          ZoneType =2
          write(36,rec=iwrite) ZoneType !ZoneType 0=ORDERED,  1=FELINESEG,  2=FETRIANGLE, 3=FEQUADRILATERAL, 4=FETETRAHEDRON,  5=FEBRICK, 6=FEPOLYGON, 7=FEPOLYHEDRON
          iwrite = iwrite+1
          VarLoc = 1
          write(36,rec=iwrite) VarLoc !Specify Var Location.  0 = Don’t specify, all data is locatedat the nodes. 1 = Specify
          iwrite = iwrite+1
          if (VarLoc.eq.1) then
            nodeCELLcenter(1) = 0
            nodeCELLcenter(2) = 0
            do i=1,numvar
              write(36,rec=iwrite) nodeCELLcenter(i) !0 = Node, 1 = Cell Centered (See note 5.)
              iwrite = iwrite+1
            enddo
          endif
          write(36,rec=iwrite) 0 !Are raw local 1-to-1 face neighbors supplied? (0=FALSE 1=TRUE).
          iwrite = iwrite+1
          write(36,rec=iwrite) 0 !Number of miscellaneous user-defined  face neighbor connections (value >= 0). This value is in addition to  the face neighbors
          iwrite = iwrite+1
          write(36,rec=iwrite) nodi
          iwrite = iwrite+1
          write(36,rec=iwrite) maglie
          iwrite = iwrite+1
          write(36,rec=iwrite) 0,0,0 !ICellDim,JCellDim, KCellDim (for future use; set to zero)
          iwrite = iwrite+3
          write(36,rec=iwrite)  0 !1=Auxiliary name/value pair to follow ;  0=No more Auxiliary name/value pairs.
          iwrite = iwrite+1
          !v. Geometries
          !write(36,rec=iwrite) 399.0e0 ! Geometry marker. Value = 399.0
          !iwrite = iwrite+1
          !vi. Text
          !write(36,rec=iwrite) 499.0e0 !Text marker. Value=499.0
          !iwrite = iwrite+1
          !vii.CustomLabel
          !write(36,rec=iwrite) 599.0e0 !CustomLabel Marker; F=599
          !iwrite = iwrite+1
          !viii.UserRec
          !write(36,rec=iwrite) 699.0e0 !UserRec Marker; F=699
          !iwrite = iwrite+1
          !ix. Dataset Auxiliary data.
          !write(36,rec=iwrite) 799.0e0 !DataSetAux Marker; F=799.0
          !iwrite = iwrite+1
          !x. Variable Auxiliary data.
          !write(36,rec=iwrite) 999.0e0 !VarAux Marker; F=899.0
          !iwrite = iwrite+1
          write(36,rec=iwrite) 357.0e0  !EOHMARKER, value=357.0
          iwrite = iwrite+1
          !II. DATA SECTION
          write(36,rec=iwrite) 299.0e0 !Zone marker Value = 299.0
          iwrite = iwrite+1
          !i. For both ordered and fe zones:
          DO I=1,NUMVAR
            write(36,rec=iwrite) 1  !Variable data format (INT32*N),  N=Total number of vars 1=Float, 2=Double, 3=LongInt,4=ShortInt, 5=Byte,  6=Bit
            iwrite = iwrite+1
          ENDDO
          write(36,rec=iwrite) 0  !Has passive variables: 0 = no, 1 = yes.
          iwrite = iwrite+1
          write(36,rec=iwrite) 0  !Has variable sharing 0 = no, 1 = yes.
          iwrite = iwrite+1
          write(36,rec=iwrite) -1 !Zero based zone number to share  connectivity list with (-1 = no sharing). FEPOLYGON and FEPOLYHEDRON  zones use this zone number to share face map data.
          iwrite = iwrite+1
          !Compressed list of min/max pairs for each non-shared and non-passive variables
          CSprint(1:nodi,1) = x(1:nodi); 
          CSprint(1:nodi,2) = y(1:nodi);
          DO I=1,numvar
            if (nodeCELLcenter(i).eq.0) then
              jmax = nodi
            elseif (nodeCELLcenter(i).eq.1) then
              jmax = maglie
            endif
            DBLEmin = DBLE(MINVAL(CSprint(1:jmax,i)))
            DBLEmax = DBLE(MAXVAL(CSprint(1:jmax,i)))
            write(36,rec=iwrite) DBLEmin
            iwrite = iwrite+2
            write(36,rec=iwrite) DBLEmax
            iwrite = iwrite+2
            DO J=1,jmax
              write(36,rec=iwrite) CSprint(j,I)  
              iwrite = iwrite+1
            enddo
          enddo
          !ii. specific to ordered zones
          !iii. specific to fe zones
          do i=1,maglie
!            do k=1,3
!              buttaINT = n123(k,i)
!              write(36,rec=iwrite) buttaINT
!              iwrite = iwrite+1
!            enddo
            write(36,rec=iwrite) 1, 2, 4
            iwrite = iwrite+3
            write(36,rec=iwrite) 2, 5, 4
            iwrite = iwrite+3
            write(36,rec=iwrite) 3, 5, 2
            iwrite = iwrite+3
            write(36,rec=iwrite) 5, 6, 4
            iwrite = iwrite+3
          enddo
      enddo
    STOP
    END
Lupocci is offline   Reply With Quote

Old   June 8, 2012, 17:47
Default Missing DataPacking parameter
  #2
New Member
 
wen long
Join Date: May 2012
Posts: 29
Rep Power: 13
wenlong is on a distinguished road
The document is INACCURATE although it is a 2012 version. On page 150 of the pdf file, between


+-----------+
| INT32 | ZoneType 0=ORDERED, 1=FELINESEG,
+-----------+ 2=FETRIANGLE, 3=FEQUADRILATERAL,
4=FETETRAHEDRON, 5=FEBRICK,
6=FEPOLYGON, 7=FEPOLYHEDRON

and

+-----------+
| INT32 | Specify Var Location.
+-----------+ 0 = Don’t specify, all data is located
at the nodes.
1 = Specif


The following is missing:
+-----------+
| INT32 | DataPacking 0=Block, 1=Point
+-----------+

See an earlier version of the document (line 83):

http://download.tecplot.com/tecio/360/binaryformat.txt

Hopefully this solves your problem.

Wen
wenlong is offline   Reply With Quote

Old   June 12, 2012, 14:14
Default
  #3
New Member
 
Andreas P
Join Date: Sep 2010
Posts: 26
Rep Power: 15
andreasp is on a distinguished road
seems that you are not using the tecio library for writing the .plt file.
any specific reason for that? for me the library has always worked fine. so this might help you...

best, andreas
andreasp is offline   Reply With Quote

Old   June 12, 2012, 14:49
Default
  #4
New Member
 
wen long
Join Date: May 2012
Posts: 29
Rep Power: 13
wenlong is on a distinguished road
I'm trying to get it going with matlab/octave. The tecio works fine, but I find it not convenient to call the c programs from matlab.

If you have done that, please let me know.
wenlong is offline   Reply With Quote

Old   June 12, 2012, 15:07
Default
  #5
New Member
 
Andreas P
Join Date: Sep 2010
Posts: 26
Rep Power: 15
andreasp is on a distinguished road
Sorry I don't really have experience with C functions in matlab. The only thing I know is that you need to use this MEX interface. Possibly, you are also required to use a certain compiler for your C code in order to stay compatible with the Matlab runtime libs. (For gcc I somehow believe you must not use a compiler newer than gcc 4.4... just breaking out old memories with no guarantee...)

But anyway, it should be possible (with moderate effort) to call C/C++/Fortran routines from Matlab...
andreasp is offline   Reply With Quote

Old   June 12, 2012, 16:03
Default
  #6
New Member
 
wen long
Join Date: May 2012
Posts: 29
Rep Power: 13
wenlong is on a distinguished road
Thanks! I'm 3 quarters done with writing a matlab function that will generate binary plt files (lines, surfaces, bricks, finite elements and geometries) without using tecio or mex. I will post it here for folks to use after I finish debugging.

The tecplot has now deprecated POINT type of datapacking.
wenlong is offline   Reply With Quote

Old   June 27, 2012, 19:56
Default mat2tecplot.m
  #7
New Member
 
wen long
Join Date: May 2012
Posts: 29
Rep Power: 13
wenlong is on a distinguished road
Dear all,

I finally finished and tested a matlab program that will dump data to tecplot binary format directly without using tecio. I'm loving it and here you go. Please see the attached mat2tecplot.m .

Simply unzip it and type in matlab command:

mat2tecplot

It will show you how it works.

Wen Long
Attached Files
File Type: zip mat2tecplot.zip (73.9 KB, 279 views)
wenlong is offline   Reply With Quote

Reply


Posting Rules
You may not post new threads
You may not post replies
You may not post attachments
You may not edit your posts

BB code is On
Smilies are On
[IMG] code is On
HTML code is Off
Trackbacks are Off
Pingbacks are On
Refbacks are On


Similar Threads
Thread Thread Starter Forum Replies Last Post
Installation of OpenFOAM-1.6 on Ubuntu 9.10 marval OpenFOAM Installation 2 March 17, 2010 08:33
[Gmsh] Compiling gmshFoam with OpenFOAM-1.5 BlGene OpenFOAM Meshing & Mesh Conversion 10 August 6, 2009 04:26
ParaView Compilation jakaranda OpenFOAM Installation 3 October 27, 2008 11:46
DxFoam reader update hjasak OpenFOAM Post-Processing 69 April 24, 2008 01:24
CFX4.3 -build analysis form Chie Min CFX 5 July 12, 2001 23:19


All times are GMT -4. The time now is 21:51.