forked from truongdangqe/Unstruct2D
-
Notifications
You must be signed in to change notification settings - Fork 0
/
plotSurfaces.f90
286 lines (236 loc) · 7.9 KB
/
plotSurfaces.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
!> @file plotSurfaces.f90
!!
!! Output of flow variables at the surfaces.
!
! *****************************************************************************
!
! (c) J. Blazek, CFD Consulting & Analysis, www.cfd-ca.de
! Created February 25, 2014
! Last modification: June 4, 2014
!
! *****************************************************************************
!
! This program is free software; you can redistribute it and/or
! modify it under the terms of the GNU General Public License
! as published by the Free Software Foundation; either version 2
! of the License, or (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program; if not, write to the Free Software
! Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
!
! *****************************************************************************
!> Writes out selected values at walls and symmetry boundaries in Vis2D format.
!!
subroutine PlotSurfaces
use ModDataTypes
use ModControl
use ModFiles
use ModGeometry
use ModNumerics
use ModPhysics
use ModPlotQuant
use ModInterfaces, only : ErrorMessage
implicit none
! local variables
character(chrlen) :: fname
integer :: errFlag, itype, ibegf, iendf, ibegn, iendn, ibf1, ibf2, &
nquant, nsurfs
integer :: i, ib, ibf, ibn, m
real(rtype) :: rrho, u, v, e, press, temp, c, ptot, ttot, mach, machis, &
ptloss, pratio, ptotinf, gam1, ggm1
real(rtype) :: cf, cp, visc, sx, sy, ds, sxn, syn, grdnx, grdny, grdnn, &
dvdnx, dvdny, dvdna, sgn
real(rtype) :: varout(mxquant+2)
character(20) :: citer ! Truong ajoute 29/05/2017
! *****************************************************************************
ptotinf = 0.D0
if (kflow == "E") then
gam1 = gamma - 1.D0
ggm1 = gamma/gam1
ptotinf = pinf*(1.D0+0.5D0*gam1*machinf*machinf)**ggm1
endif
! open plot file
write(fname,"(A,I5.5,A)") Trim(fnSurf),iter,".v2d"
open(unit=ifSurf, file=fname, status="unknown", action="write", iostat=errFlag)
if (errFlag /= 0) call ErrorMessage( "cannot open plot file (surfaces)" )
! Truong ajoute 20/12/2017: write skin friction coefficients in Tecplot format
! add
if (lquant(12) == "Y") then
write(citer,'(I8.8)') iter
open(unit = 20, file = 'SKIN_FRICTION_COEF_'//trim(citer)//'.DAT')
write(20,*) 'VARIABLES=X,Y,Cf'
endif
! end add
! header
nquant = 0
do m=1,mxquant
if (lquant(m) == "Y") nquant = nquant + 1
enddo
nsurfs = 0 ! no. of surfaces to output
do ib=1,nsegs
itype = btype(ib)
if ((itype>=300 .and. itype<600) .or. &
(itype>=800 .and. itype<900)) nsurfs = nsurfs + 1
enddo
write(ifSurf,1000) Trim(title),nsurfs,nquant+2
! names of variables
do m=1,mxquant
if (lquant(m) == "Y") then
write(ifSurf,"(A)") Trim(cquant(m))
endif
enddo
! compute quantities & write'em out
ibegf = 1
ibegn = 1
do ib=1,nsegs
iendf = ibound(1,ib)
iendn = ibound(2,ib)
itype = btype(ib)
if ((itype>=300 .and. itype<600) .or. &
(itype>=800 .and. itype<900)) then
write(ifSurf,1010) iendn-ibegn+1,Trim(bname(ib))
do ibn=ibegn,iendn
i = bnode(1,ibn)
varout(1) = x(i)
varout(2) = y(i)
rrho = 1.D0/cv(1,i)
u = cv(2,i)*rrho
v = cv(3,i)*rrho
e = cv(4,i)*rrho
press = dv(1,i)
temp = dv(2,i)
c = dv(3,i)
gam1 = dv(4,i) - 1.D0
ggm1 = dv(4,i)/gam1
if (kequs == "N") then
ibf1 = -1
ibf2 = -1
do ibf=ibegf,iendf
if (bface(1,ibf) == i) then
if (ibf1 < 0) then
ibf1 = ibf
else
ibf2 = ibf
endif
endif
if (bface(2,ibf) == i) then
if (ibf1 < 0) then
ibf1 = ibf
else
ibf2 = ibf
endif
endif
enddo
if (ibf2 < 0) ibf2 = ibf1
visc = dv(6,i)
sx = -0.5D0*(sbf(1,ibf1)+sbf(1,ibf2)) ! to point inside
sy = -0.5D0*(sbf(2,ibf1)+sbf(2,ibf2))
ds = Sqrt(sx*sx+sy*sy)
sxn = sx/ds
syn = sy/ds
grdnx = gradx(2,i)*sxn + grady(2,i)*syn
grdny = gradx(3,i)*sxn + grady(3,i)*syn
grdnn = grdnx*sxn + grdny*syn
dvdnx = grdnx - grdnn*sxn
dvdny = grdny - grdnn*syn
if (grdnx > grdny) then ! to get somehow the main flow
sgn = Sign(1.D0,grdnx)
else
sgn = Sign(1.D0,grdny)
endif
dvdna = Sqrt(dvdnx*dvdnx+dvdny*dvdny)
if (kflow == "E") then
cf = 2.D0*sgn*visc*dvdna/(rhoinf*qinf*qinf)
else
cf = 2.D0*sgn*visc*dvdna/(refrho*refvel*refvel)
endif
else
visc = 0.D0
cf = 0.D0
endif
mach = Sqrt(u*u+v*v)/c
ttot = (e+press*rrho)/dv(5,i)
ptot = press*(ttot/temp)**ggm1
if (kflow == "E") then
ptloss = 1.D0 - ptot/ptotinf
pratio = ptotinf/press
cp = 2.*(pinf-press)/(rhoinf*qinf*qinf)
else
ptloss = 1.D0 - ptot/ptinl
pratio = ptinl/press
cp = 2.*((p12rat*pout)-press)/(refrho*refvel*refvel)
endif
machis = (pratio**(1.D0/ggm1)-1.D0)*2.D0/gam1
machis = Max(machis, 0.D0)
machis = Sqrt(machis)
! ----- store quantities in varout()
nquant = 2
do m=1,mxquant
if (lquant(m) == "Y") then
nquant = nquant + 1
! --------- density
if (m == 1) then
varout(nquant) = cv(1,i)
! --------- u-velocity
else if (m == 2) then
varout(nquant) = u
! --------- v-velocity
else if (m == 3) then
varout(nquant) = v
! --------- static pressure
else if (m == 4) then
varout(nquant) = press
! --------- total pressure
else if (m == 5) then
varout(nquant) = ptot
! --------- static temperature
else if (m == 6) then
varout(nquant) = temp
! --------- total temperature
else if (m == 7) then
varout(nquant) = ttot
! --------- local Mach number
else if (m == 8) then
varout(nquant) = mach
! --------- isentropic Mach number
else if (m == 9) then
varout(nquant) = machis
! --------- total pressure loss
else if (m == 10) then
varout(nquant) = ptloss
! --------- laminar viscosity coefficient
else if (m == 11) then
varout(nquant) = visc
! --------- skin friction coefficient
else if (m == 12) then
varout(nquant) = cf
! --------- pressure coefficient
else if (m == 13) then
varout(nquant) = cp
endif
endif
enddo
write(ifSurf,1020) (varout(m), m=1,nquant)
! Truong ajoute 20/12/2017
! add
if (lquant(12) == "Y") then
write(20,*) varout(1), varout(2), cf
end if
! end add
enddo ! node
endif ! itype
ibegf = iendf + 1
ibegn = iendn + 1
enddo ! ib
close(unit=ifSurf)
close(20)
1000 format(A,/,"1",/,"Boundaries",/,I3,I3,/,"x [m]",/,"y [m]")
1010 format(I6," 0",/,"0 0 0",/,A)
1020 format(1P,20E16.8)
end subroutine PlotSurfaces