CalculiX  2.13
A Free Software Three-Dimensional Structural Finite Element Program
tee.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine tee (node1, node2, nodem, nelem, lakon, kon, ipkon, nactdog, identity, ielprop, prop, iflag, v, xflow, f, nodef, idirf, df, cp, r, physcon, numf, set, mi, ider, ttime, time, iaxial)
 

Function/Subroutine Documentation

◆ tee()

subroutine tee ( integer  node1,
integer  node2,
integer  nodem,
integer  nelem,
character*8, dimension(*)  lakon,
integer, dimension(*)  kon,
integer, dimension(*)  ipkon,
integer, dimension(0:3,*)  nactdog,
logical  identity,
integer, dimension(*)  ielprop,
real*8, dimension(*)  prop,
integer  iflag,
real*8, dimension(0:mi(2),*)  v,
real*8  xflow,
real*8  f,
integer, dimension(*)  nodef,
integer, dimension(*)  idirf,
real*8, dimension(*)  df,
real*8  cp,
real*8  r,
real*8, dimension(*)  physcon,
integer  numf,
character*81, dimension(*)  set,
integer, dimension(2)  mi,
integer  ider,
real*8  ttime,
real*8  time,
integer  iaxial 
)
22 !
23 ! A tee split element(zeta calculation according to Idel'chik)
24 ! Written by Yavor Dobrev
25 !
26  implicit none
27 !
28  logical identity
29 !
30  character*81 set(*)
31  character*8 lakon(*)
32 !
33  integer
34 ! Number of the current element
35  &nelem,
36 ! Array with the degrees of freedom
37  &nactdog(0:3,*),
38 ! Number of the first node of the element
39  &node1,
40 ! Number of the second node of the element
41  &node2,
42 ! Number of the middle node of the element
43  &nodem,
44 ! Number of the derivatives
45  &numf,
46 ! Array with all nodes
47  &kon(*),
48 ! Array, which shows where a given element starts in kon
49  &ipkon(*),
50 ! Array which shows where the properties of a given element
51 ! begin in prop
52  &ielprop(*),
53 ! Contains the nodes where the dependant varibles for this
54 ! element are
55  &nodef(*),
56 ! Contains the type of the dependant variables
57  &idirf(*),
58 ! The starting index of the given element#s properties in prop
59  &index,
60 ! Shows where we are in the program
61  &iflag,
62 ! 1 for normal, -1 for inverted flow
63  &inv,
64 ! Shows how many types of DOF there are
65  &mi(2),
66 ! This is the number of the previous element this element is
67 ! connected to
68  &nelem1,
69 ! The middle node of the previous element
70  &nodem1,
71 ! 0 if a residual is to be calculated, 1 for derivatives
72  &ider,chan_num,icase,iaxial
73 !
74  real*8
75 ! Array with the properties of all elements
76  &prop(*),
77 ! Array with the values of the unknown variables
78  &v(0:mi(2),*),
79 ! Mass flow in the current element
80  &xflow,
81 ! Residual value
82  &f,
83 ! Array with the derivatives
84  &df(*),
85 ! Isentropic exponent
86  &kappa,
87 ! Gas constant
88  &r,
89 ! Specific heat
90  &cp,
91 ! Total temperatures and total pressures
92  &tt1,tt2,pt1,pt2,
93 ! Array with physical constants
94  &physcon(*),
95 ! Kappa terms
96  &km1,kp1,kdkm1,tdkp1,
97 ! Pressure ratios
98  &pt2pt1,pt2pt1_crit,
99 ! Areas
100  &a,a1,a2,
101 ! Factor zeta_fac for influencing zeta
102 ! zeta_eff = zeta_fac*zeta
103  &zeta_fac,
104 ! Variable for the function result
106 ! Mass flow in the previuos element
107  &xflow1,
108 ! Mass flow in the current element(same as xflow)
109  &xflow2,ts0,pspt0,pspt2,m1,m2,ts2,ttime,time
110 !
111  index=ielprop(nelem)
112 !
113  if(iflag.eq.0) then
114 !
115 ! Checking for degrees of freedom in the element
116 !
117  identity=.true.
118  if(nactdog(2,node1).ne.0)then
119  identity=.false.
120  elseif(nactdog(2,node2).ne.0)then
121  identity=.false.
122  elseif(nactdog(1,nodem).ne.0)then
123  identity=.false.
124 !
125  endif
126 !
127  elseif(iflag.eq.1)then
128 !
129 ! Calculating the initial mass flow in the element
130 !
131 ! Some kappa terms
132  kappa=(cp/(cp-r))
133  kp1=kappa+1d0
134  km1=kappa-1d0
135  kdkm1=kappa/km1
136  tdkp1=2.d0/kp1
137 !
138 ! Get the element properties
139 ! Cross sections
140  if(nelem.eq.nint(prop(index+2))) then
141  a=prop(index+5)
142  elseif(nelem.eq.nint(prop(index+3)))then
143  a=prop(index+6)
144  endif
145  zeta_fac=prop(index+11)
146 !
147 ! Pressures
148  pt1=v(2,node1)
149  pt2=v(2,node2)
150 !
151 ! Check for inverted flow
152  if(pt1.ge.pt2) then
153  inv=1
154  tt1=v(0,node1)-physcon(1)
155  tt2=v(0,node2)-physcon(1)
156  else
157  inv=-1
158  pt1=v(2,node2)
159  pt2=v(2,node1)
160  tt1=v(0,node2)-physcon(1)
161  tt2=v(0,node1)-physcon(1)
162  endif
163 !
164 ! Pressure ratios
165  pt2pt1=pt2/pt1
166  pt2pt1_crit=tdkp1**kdkm1
167 !
168  if(pt2pt1.gt.pt2pt1_crit) then
169 ! Subcritical case
170  xflow=inv*pt1*a*dsqrt(2.d0*kdkm1*pt2pt1**(2.d0/kappa)
171  & *(1.d0-pt2pt1**(1.d0/kdkm1))/r)/dsqrt(tt1)
172  else
173 ! Critical case
174  xflow=inv*pt1*a*dsqrt(kappa/r)*tdkp1**(kp1/(2.d0*km1))/
175  & dsqrt(tt1)
176  endif
177 !
178  elseif(iflag.eq.2)then
179 !
180 ! Calculation of residual/derivatives
181 !
182 ! Number of dependant variables(corresponding derivatives)
183  numf=6
184 !
185 ! Calculate kappa
186  kappa=(cp/(cp-r))
187 !
188 ! setting icase (always adiabatic)
189  icase=0;
190 !
191 ! Inlet conditions are the same for both branches
192 !
193 ! Determining the previous element as
194 ! the incoming mass flow is defined there
195  nelem1=nint(prop(index+1))
196  nodem1=kon(ipkon(nelem1)+2)
197 !
198 ! Inlet conditions
199  pt1=v(2,node1)
200  tt1=v(0,node1)-physcon(1)
201  xflow1=v(1,nodem1)*iaxial
202  a1=prop(index+4)
203 !
204 ! Outlet conditions
205  tt2=v(0,node2)
206  xflow2=v(1,nodem)*iaxial
207  pt2=v(2,node2)
208  if(nelem.eq.nint(prop(index+2))) then
209  a2=prop(index+5)
210  zeta_fac=prop(index+11)
211  elseif(nelem.eq.nint(prop(index+3))) then
212  a2=prop(index+6)
213  zeta_fac=prop(index+12)
214  endif
215 ! zeta_fac = prop(index+11)
216 !
217 ! Set the node numbers for the degrees of freedom
218  nodef(1)=node1
219  nodef(2)=node1
220  nodef(3)=nodem1
221  nodef(4)=nodem
222  nodef(5)=node2
223  nodef(6)=node2
224 !
225 ! Sets the types of the degrees of freedom
226  idirf(1)=2
227  idirf(2)=0
228  idirf(3)=1
229  idirf(4)=1
230  idirf(5)=2
231  idirf(6)=0
232 !
233 ! Calculate residual or derivatives
234  if(ider.eq.0) then
235 ! Residual
236  f=calc_residual_tee(pt1,tt1,xflow1,xflow2,pt2,
237  & tt2,a1,a2,zeta_fac,kappa,r,ider,iflag)
238  else
239 ! Derivatives
240  call calc_ider_tee(df,pt1,tt1,xflow1,xflow2,pt2,
241  & tt2,a1,a2,zeta_fac,kappa,r,ider,iflag)
242  endif
243  elseif(iflag.eq.3) then
244 !
245 ! Element output
246 !
247 ! Calculate kappa
248  kappa=(cp/(cp-r))
249 !
250 ! setting icase (always adiabatic)
251  icase=0;
252 !
253 ! Inlet conditions are the same for both branches
254 !
255 ! Determining the previous element as
256 ! the incoming mass flow is defined there
257  nelem1=nint(prop(index+1))
258  nodem1=kon(ipkon(nelem1)+2)
259 !
260 ! Inlet conditions
261  pt1=v(2,node1)
262  tt1=v(0,node1)-physcon(1)
263  xflow1=v(1,nodem1)*iaxial
264  a1=prop(index+4)
265 !
266 ! Outlet conditions
267  tt2=v(0,node2)
268  xflow2=v(1,nodem)*iaxial
269  pt2=v(2,node2)
270  if(nelem.eq.nint(prop(index+2))) then
271  a2=prop(index+5)
272  chan_num=1
273  zeta_fac=prop(index+11)
274  elseif(nelem.eq.nint(prop(index+3))) then
275  a2=prop(index+6)
276  chan_num=2
277  zeta_fac=prop(index+12)
278  endif
279 ! zeta_fac = prop(index+11)
280 !
281 ! Write the main information about the element
282 !
283 
284 ! Flow velocity at inlet
285  call ts_calc(xflow1,tt1,pt1,kappa,r,a1,ts0,icase)
286  pspt0=(ts0/tt1)**(kappa/(kappa-1))
287 ! Calculate Mach numbers
288  call machpi(m1,pspt0,kappa,r)
289  call ts_calc(xflow2,tt2,pt2,kappa,r,a2,ts2,icase)
290 ! Pressure ratio
291  pspt2=(ts2/tt2)**(kappa/(kappa-1))
292  call machpi(m2,pspt2,kappa,r)
293 !
294  write(1,*) ''
295  write(1,55) ' from node ',node1,
296  & ' to node ', node2,': air massflow rate=' ,xflow
297 !
298  write(1,56)' Inlet node ',node1,': Tt1= ',tt1,
299  & ' , Ts1= ',ts0,' , Pt1= ',pt1,
300  & ', M1= ',m1
301  write(1,*)' Element ',nelem,lakon(nelem)
302  & ,', Branch ',chan_num
303 !
304  55 format(1x,a,i6,a,i6,a,e11.4,a)
305  56 format(1x,a,i6,a,e11.4,a,e11.4,a,e11.4,a,e11.4)
306 !
307 ! Set ider to calculate the residual
308  ider=0
309 !
310 ! Calculate the element one last time with enabled output
311  f=calc_residual_tee(pt1,tt1,xflow1,xflow2,pt2,
312  & tt2,a1,a2,zeta_fac,kappa,r,ider,iflag)
313 !
314  write(1,56)' Outlet node ',node2,': Tt2= ',tt2,
315  & ' , Ts2= ',ts2,' , Pt2= ',pt2,
316  & ', M2= ',m2
317  endif
318 !
319  xflow=xflow/iaxial
320  df(3)=df(3)*iaxial
321  df(4)=df(4)*iaxial
322 !
323  return
subroutine df(x, u, uprime, rpar, nev)
Definition: subspace.f:133
subroutine ts_calc(xflow, Tt, Pt, kappa, r, A, Ts, icase)
Definition: ts_calc.f:20
subroutine calc_ider_tee(df, pt1, Tt1, xflow1, xflow2, pt2, Tt2, A1, A2, zeta_fac, kappa, R, ider, iflag)
Definition: calc_ider_tee.f:22
subroutine machpi(MACH, PI, kappa, rgas)
Definition: machpi.f:23
static double * e11
Definition: radflowload.c:42
real *8 function calc_residual_tee(pt1, Tt1, xflow1, xflow2, pt2, Tt2, A1, A2, zeta_fac, kappa, R, ider, iflag)
Definition: calc_residual_tee.f:20
Hosted by OpenAircraft.com, (Michigan UAV, LLC)