61 TYPE(t_region
),
POINTER :: region
67 CHARACTER(CHRLEN) :: ifilename,sectionstring,rcsidentstring
71 INTEGER :: errorflag,ifile,nvars
72 REAL(RFREAL) :: currenttime
73 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: tv, tcv, vort
74 REAL(RFREAL),
DIMENSION(:),
POINTER :: lens
80 rcsidentstring =
'$RCSfile: TURB_rFLU_WriteSolutionASCII.F90,v $ $Revision: 1.5 $'
82 global => region%global
85 'TURB_rFLU_WriteSolutionASCII.F90')
87 IF ( global%myProcid == masterproc .AND. &
88 global%verbLevel > verbose_none )
THEN
89 WRITE(stdout,
'(A,1X,A)') solver_name,
'Writing ASCII turbulence file...'
92 IF ( global%flowType == flow_unsteady )
THEN
94 region%iRegionGlobal,global%currentTime, &
97 IF ( global%myProcid == masterproc .AND. &
98 global%verbLevel > verbose_none )
THEN
99 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
101 WRITE(stdout,
'(A,3X,A,1X,1PE11.5)') solver_name,
'Current time:', &
106 region%iRegionGlobal,global%currentIter,ifilename)
108 IF ( global%myProcid == masterproc .AND. &
109 global%verbLevel > verbose_none )
THEN
110 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
112 WRITE(stdout,
'(A,3X,A,1X,I6.6)') solver_name,
'Current iteration '// &
113 'number:',global%currentIter
118 OPEN(ifile,file=ifilename,
form=
"FORMATTED",
status=
"UNKNOWN", &
120 global%error = errorflag
121 IF ( global%error /= err_none )
THEN
122 CALL
errorstop(global,err_file_open,__line__,ifilename)
129 IF ( global%myProcid == masterproc .AND. &
130 global%verbLevel > verbose_low )
THEN
131 WRITE(stdout,
'(A,3X,A)') solver_name,
'Header information...'
134 sectionstring =
'# ROCTURB solution file'
135 WRITE(ifile,
'(A)') sectionstring
137 sectionstring =
'# Precision and range'
138 WRITE(ifile,
'(A)') sectionstring
139 WRITE(ifile,
'(2(I8))')
precision(1.0_rfreal),range(1.0_rfreal)
141 sectionstring =
'# Initial residual'
142 WRITE(ifile,
'(A)') sectionstring
143 WRITE(ifile,
'(E23.16)') global%resInit
145 sectionstring =
'# Physical time'
146 WRITE(ifile,
'(A)') sectionstring
147 WRITE(ifile,
'(E23.16)') global%currentTime
149 sectionstring =
'# Esg1Sum'
150 WRITE(ifile,
'(A)') sectionstring
151 WRITE(ifile,
'(E23.16)') global%esg1Sum
153 sectionstring =
'# Esg4Sum'
154 WRITE(ifile,
'(A)') sectionstring
155 WRITE(ifile,
'(E23.16)') global%esg4Sum
161 nvars = region%turbInput%nOutField
165 sectionstring =
'# Dimensions'
166 WRITE(ifile,
'(A)') sectionstring
167 WRITE(ifile,
'(2(I8))')
grid%nCellsTot,nvars
173 IF ( global%myProcid == masterproc .AND. &
174 global%verbLevel > verbose_low )
THEN
175 WRITE(stdout,
'(A,3X,A)') solver_name,
'Eddy viscosity...'
178 sectionstring =
'# Eddy viscosity'
179 WRITE(ifile,
'(A)') sectionstring
181 IF (region%turbInput%modelClass == model_les)
THEN
183 WRITE(ifile,
'(5(E23.16))') (tv(tv_mixt_muet,
j),
j=1,
grid%nCellsTot)
184 ELSEIF (region%turbInput%modelClass == model_rans)
THEN
185 tcv => region%turb%cv
186 WRITE(ifile,
'(5(E23.16))') (tcv(cv_sa_nutil,
j),
j=1,
grid%nCellsTot)
193 IF ( nvars > 1 )
THEN
194 IF ( global%myProcid == masterproc .AND. &
195 global%verbLevel > verbose_low )
THEN
196 WRITE(stdout,
'(A,3X,A)') solver_name,
'Total vorticity...'
199 sectionstring =
'# Total vorticity'
200 WRITE(ifile,
'(A)') sectionstring
202 vort => region%turb%vort
203 WRITE(ifile,
'(5(E23.16))') (
sqrt( vort(xcoord,
j)**2 + &
204 vort(ycoord,
j)**2 + &
205 vort(zcoord,
j)**2 ),
j=1,
grid%nCellsTot)
212 IF ( nvars > 2 )
THEN
213 IF (region%turbInput%modelClass == model_rans)
THEN
215 IF ( global%myProcid == masterproc .AND. &
216 global%verbLevel > verbose_low )
THEN
217 WRITE(stdout,
'(A,3X,A)') solver_name,
'Model length scale...'
220 sectionstring =
'# RANS length scale'
221 WRITE(ifile,
'(A)') sectionstring
223 lens => region%turb%lens
224 WRITE(ifile,
'(5(E23.16))') (lens(
j),
j=1,
grid%nCellsTot)
232 IF ( global%myProcid == masterproc .AND. &
233 global%verbLevel > verbose_low )
THEN
234 WRITE(stdout,
'(A,3X,A)') solver_name,
'End marker...'
237 sectionstring =
'# End'
238 WRITE(ifile,
'(A)') sectionstring
244 CLOSE(ifile,iostat=errorflag)
245 global%error = errorflag
246 IF ( global%error /= err_none )
THEN
247 CALL
errorstop(global,err_file_close,__line__,ifilename)
250 IF ( global%myProcid == masterproc .AND. &
251 global%verbLevel > verbose_none )
THEN
252 WRITE(stdout,
'(A,1X,A)') solver_name,
'Writing ASCII flow file done.'
subroutine registerfunction(global, funName, fileName)
int status() const
Obtain the status of the attribute.
subroutine turb_rflu_writesolutionascii(region)
**********************************************************************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)
subroutine deregisterfunction(global)
subroutine buildfilenamesteady(global, dest, ext, id, it, fileName)
subroutine buildfilenameunsteady(global, dest, ext, id, tm, fileName)