Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TFLU_WriteFluDimens.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 dimension file for Rocflu run.
26 !
27 ! Description: none.
28 !
29 ! Notes: none.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: TFLU_WriteFluDimens.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 writefludimens( 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 :: igpatch
54 
55 ! ... local variables
56  CHARACTER(CHRLEN) :: ifilename, sectionstring
57 
58  INTEGER :: errorflag, ifile
59  REAL(RFREAL) :: ratiomax2tot
60 
61 ! ******************************************************************************
62 
63  CALL registerfunction(global,'WriteFluDimens',&
64  'TFLU_WriteFluDimens.F90')
65 
66 ! start ------------------------------------------------------------------------
67 
68  IF ( global%verbLevel > verbose_none ) THEN
69  WRITE(stdout,'(A,1X,A)') solver_name,'Writing Rocflu dimension file...'
70  END IF
71 
72  ifile = if_dims
73 
74  WRITE(ifilename,'(A,I5.5)') &
75  trim(global%outDir)//trim(global%casename)//'.dim_',0
76 
77  OPEN(ifile,file=ifilename,form="FORMATTED",status="UNKNOWN",iostat=errorflag)
78  global%error = errorflag
79 
80  IF ( global%error /= err_none ) THEN
81  CALL errorstop(global,err_file_open,__line__,ifilename)
82  END IF ! global%error
83 
84 ! header and general information -----------------------------------------------
85 
86  ratiomax2tot = 1.2_rfreal ! Hard-coded for now
87 
88  IF ( global%verbLevel > verbose_low ) THEN
89  WRITE(stdout,'(A,3X,A)') solver_name,'Header information...'
90  END IF ! global%verbLevel
91 
92  sectionstring = '# ROCFLU dimensions file'
93  WRITE(ifile,'(A)') trim(sectionstring)
94 
95  sectionstring = '# Vertices'
96  WRITE(ifile,'(A)') trim(sectionstring)
97  WRITE(ifile,'(3(I8))') global%tofluNVerts, global%tofluNVerts, &
98  int(ratiomax2tot*global%tofluNVerts)
99 
100  sectionstring = '# Cells'
101  WRITE(ifile,'(A)') trim(sectionstring)
102  WRITE(ifile,'(3(I8))') global%tofluNHexs, global%tofluNHexs, &
103  int(ratiomax2tot*global%tofluNHexs)
104 
105  sectionstring = '# Tetrahedra'
106  WRITE(ifile,'(A)') trim(sectionstring)
107  WRITE(ifile,'(3(I8))') 0, 0, 0
108 
109  sectionstring = '# Hexahedra'
110  WRITE(ifile,'(A)') trim(sectionstring)
111  WRITE(ifile,'(3(I8))') global%tofluNHexs, global%tofluNHexs, &
112  int(ratiomax2tot*global%tofluNHexs)
113 
114  sectionstring = '# Prisms'
115  WRITE(ifile,'(A)') trim(sectionstring)
116  WRITE(ifile,'(3(I8))') 0, 0, 0
117 
118  sectionstring = '# Pyramids'
119  WRITE(ifile,'(A)') trim(sectionstring)
120  WRITE(ifile,'(3(I8))') 0, 0, 0
121 
122 ! sectionString = '# Faces'
123 ! WRITE(iFile,'(A)') TRIM(sectionString)
124 ! WRITE(iFile,'(2(I8))') global%tofluNFaces, global%tofluNFaces
125 
126 ! sectionString = '# Edges'
127 ! WRITE(iFile,'(A)') TRIM(sectionString)
128 ! WRITE(iFile,'(2(I8))') global%tofluNEdges, global%tofluNEdges
129 
130  sectionstring = '# Patches'
131  WRITE(ifile,'(A)') trim(sectionstring)
132  WRITE(ifile,'(2(I8))') global%tofluNPatches, global%tofluNPatches
133 
134  DO igpatch = 1,global%tofluNPatches
135 
136  WRITE(ifile,'(5(I8))') igpatch, 0, 0, &
137  global%tofluNbFaces(igpatch), &
138  global%tofluNbFaces(igpatch)
139  END DO ! iPatch
140 
141  sectionstring = '# Borders'
142  WRITE(ifile,'(A)') trim(sectionstring)
143  WRITE(ifile,'(1(I8))') 0
144 
145 ! end marker -------------------------------------------------------------------
146 
147  IF ( global%verbLevel > verbose_low ) THEN
148  WRITE(stdout,'(A,3X,A)') solver_name,'End marker...'
149  END IF
150 
151  sectionstring = '# End'
152  WRITE(ifile,'(A)') trim(sectionstring)
153 
154 ! close file -------------------------------------------------------------------
155 
156  CLOSE(ifile,iostat=errorflag)
157  global%error = errorflag
158  IF ( global%error /= err_none ) THEN
159  CALL errorstop(global,err_file_close,__line__,ifilename)
160  END IF
161 
162  IF ( global%verbLevel > verbose_none ) THEN
163  WRITE(stdout,'(A,1X,A)') solver_name,'Writing Rocflu dimension file done.'
164  END IF
165 
166 ! finalize ---------------------------------------------------------------------
167 
168  CALL deregisterfunction( global )
169 
170 END SUBROUTINE writefludimens
171 
172 ! ******************************************************************************
173 !
174 ! RCS Revision history:
175 !
176 ! $Log: TFLU_WriteFluDimens.F90,v $
177 ! Revision 1.4 2008/12/06 08:44:53 mtcampbe
178 ! Updated license.
179 !
180 ! Revision 1.3 2008/11/19 22:18:04 mtcampbe
181 ! Added Illinois Open Source License/Copyright
182 !
183 ! Revision 1.2 2005/12/21 19:18:18 wasistho
184 ! modified to adapt changes in Rocflu
185 !
186 ! Revision 1.1 2004/12/03 02:59:30 wasistho
187 ! added prefix
188 !
189 ! Revision 1.1 2004/12/03 00:58:20 wasistho
190 ! lower to upper case
191 !
192 ! Revision 1.1 2004/08/18 02:15:12 wasistho
193 ! added new routines to create dimension file
194 !
195 !
196 ! ******************************************************************************
197 
198 
199 
200 
201 
202 
203 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine writefludimens(global)
**********************************************************************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
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469