Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TFLU_WriteFluGrid.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 ! ******************************************************************************
24 !
25 ! Purpose: write unstructured grid file in Rocflu format.
26 !
27 ! Description: none.
28 !
29 ! Notes: currently only ASCII Rocflu format is supported.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: TFLU_WriteFluGrid.F90,v 1.4 2008/12/06 08:44:53 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2004 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
39 SUBROUTINE writeflugrid( global )
40 
41  USE modparameters
42  USE moddatatypes
43  USE moderror
44  USE modglobal, ONLY: t_global
45  USE modmpi
46 
47  IMPLICIT NONE
48 
49 ! ... parameters
50  TYPE(t_global), POINTER :: global
51 
52 ! ... loop variables
53  INTEGER :: ipatch, i, j, k
54 
55 ! ... local variables
56  CHARACTER(CHRLEN) :: ifilename, sectionstring
57 
58  INTEGER :: errorflag, ifile
59  INTEGER :: ntets, npris, npyrs, vertflag, hexflag
60  INTEGER :: nbtris, nbquads, nbverts, bvflag
61 
62 ! ******************************************************************************
63 
64  CALL registerfunction(global,'WriteFluGrid',&
65  'TFLU_WriteFluGrid.F90')
66 
67 ! start ------------------------------------------------------------------------
68 
69  IF ( global%verbLevel > verbose_none ) THEN
70  WRITE(stdout,'(A,1X,A)') solver_name,'Writing ASCII Rocflu grid file...'
71  END IF
72 
73  ifile = if_grid
74 
75  WRITE(ifilename,'(A,I5.5)') &
76  trim(global%outDir)//trim(global%casename)//'.grda_',0
77 
78  OPEN(ifile,file=ifilename,form="FORMATTED",status="UNKNOWN",iostat=errorflag)
79  global%error = errorflag
80 
81  IF ( global%error /= err_none ) THEN
82  CALL errorstop(global,err_file_open,__line__,ifilename)
83  END IF ! global%error
84 
85 ! header and general information -----------------------------------------------
86 
87  IF ( global%verbLevel > verbose_low ) THEN
88  WRITE(stdout,'(A,3X,A)') solver_name,'Header information...'
89  END IF ! global%verbLevel
90 
91  sectionstring = '# ROCFLU grid file'
92  WRITE(ifile,'(A)') trim(sectionstring)
93 
94  sectionstring = '# Precision and range'
95  WRITE(ifile,'(A)') trim(sectionstring)
96  WRITE(ifile,'(2(I8))') precision(1.0_rfreal),range(1.0_rfreal)
97 
98  sectionstring = '# Physical time'
99  WRITE(ifile,'(A)') trim(sectionstring)
100  WRITE(ifile,'(E23.16)') global%currentTime
101 
102 ! dimensions -------------------------------------------------------------------
103 
104  ntets = 0
105  npris = 0
106  npyrs = 0
107  sectionstring = '# Dimensions'
108  WRITE(ifile,'(A)') trim(sectionstring)
109  WRITE(ifile,'(5(I8))') global%tofluNVerts,ntets,global%tofluNHexs, &
110  npris,npyrs
111 
112 ! coordinates ------------------------------------------------------------------
113 
114  IF ( global%verbLevel > verbose_none ) THEN
115  WRITE(stdout,'(A,3X,A)') solver_name,'Coordinates...'
116  END IF
117 
118  sectionstring = '# Coordinates'
119  WRITE(ifile,'(A)') trim(sectionstring)
120  DO i = 1,3
121  WRITE(ifile,'(5(E23.16))') (global%tofluXyz(i,j),j=1,global%tofluNVerts)
122  END DO
123 
124 ! vertFlag = 1
125 ! WRITE(iFile,'(10(I8))') (vertFlag,j=1,global%tofluNVerts)
126 
127 ! connectivity -----------------------------------------------------------------
128 
129  IF ( global%tofluNHexs > 0 ) THEN
130  IF ( global%verbLevel > verbose_low ) THEN
131  WRITE(stdout,'(A,3X,A)') solver_name,'Hexahedra...'
132  END IF
133 
134  sectionstring = '# Hexahedra'
135  WRITE(ifile,'(A)') trim(sectionstring)
136  DO i = 1,8
137  WRITE(ifile,'(10(I8))') (global%tofluHex2v(i,j),j=1,global%tofluNHexs)
138  END DO ! i
139 
140 ! hexFlag = 1
141 ! WRITE(iFile,'(10(I8))') (hexFlag,j=1,global%tofluNHexs)
142  END IF ! nHexs
143 
144 ! boundary information ---------------------------------------------------------
145 
146  IF ( global%verbLevel > verbose_low ) THEN
147  WRITE(stdout,'(A,3X,A)') solver_name,'Boundary information...'
148  END IF
149 
150  sectionstring = '# Boundaries'
151  WRITE(ifile,'(A)') trim(sectionstring)
152  WRITE(ifile,'(I8)') global%tofluNPatches
153 
154  DO ipatch = 1, global%tofluNPatches
155  nbtris = 0
156  nbquads = global%tofluNbFaces(ipatch)
157 ! nBVerts = global%tofluNbVerts(iPatch)
158 
159 ! WRITE(iFile,'(3(I8))') nBTris, nBQuads, nBVerts
160  WRITE(ifile,'(3(I8))') nbtris, nbquads
161 
162  IF ( nbquads > 0 ) THEN
163  DO j = 1,4
164  WRITE(ifile,'(10(I8))') (global%tofluQuad2v(j,k,ipatch),k=1,nbquads)
165  END DO ! j
166  END IF ! bound
167 
168 ! WRITE(iFile,'(10(I8))') (global%tofluBLoc2g(k,iPatch),k=1,nBVerts)
169 
170 ! bvFlag = 1
171 ! WRITE(iFile,'(10(I8))') (bvFlag,k=1,nBVerts)
172  ENDDO ! iPatch
173 
174 ! end marker -------------------------------------------------------------------
175 
176  IF ( global%verbLevel > verbose_low ) THEN
177  WRITE(stdout,'(A,3X,A)') solver_name,'End marker...'
178  END IF
179 
180  sectionstring = '# End'
181  WRITE(ifile,'(A)') trim(sectionstring)
182 
183 ! close file -------------------------------------------------------------------
184 
185  CLOSE(ifile,iostat=errorflag)
186  global%error = errorflag
187  IF ( global%error /= err_none ) THEN
188  CALL errorstop(global,err_file_close,__line__,ifilename)
189  END IF
190 
191  IF ( global%verbLevel > verbose_none ) THEN
192  WRITE(stdout,'(A,1X,A)') solver_name,'Writing ASCII Rocflu grid file done.'
193  END IF
194 
195 ! finalize ---------------------------------------------------------------------
196 
197  CALL deregisterfunction( global )
198 
199 END SUBROUTINE writeflugrid
200 
201 ! ******************************************************************************
202 !
203 ! RCS Revision history:
204 !
205 ! $Log: TFLU_WriteFluGrid.F90,v $
206 ! Revision 1.4 2008/12/06 08:44:53 mtcampbe
207 ! Updated license.
208 !
209 ! Revision 1.3 2008/11/19 22:18:04 mtcampbe
210 ! Added Illinois Open Source License/Copyright
211 !
212 ! Revision 1.2 2005/12/21 19:18:30 wasistho
213 ! modified to adapt changes in Rocflu
214 !
215 ! Revision 1.1 2004/12/03 02:59:30 wasistho
216 ! added prefix
217 !
218 ! Revision 1.1 2004/12/03 00:58:20 wasistho
219 ! lower to upper case
220 !
221 ! Revision 1.1 2004/08/18 02:15:12 wasistho
222 ! added new routines to create dimension file
223 !
224 ! Revision 1.1.1.1 2004/08/17 01:41:39 wasistho
225 ! initial checkin
226 !
227 !
228 ! ******************************************************************************
229 
230 
231 
232 
233 
234 
235 
j indices k indices k
Definition: Indexing.h:6
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine writeflugrid(global)
blockLoc i
Definition: read.cpp:79
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE form
j indices j
Definition: Indexing.h:6
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469