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

Go to the source code of this file.

Functions/Subroutines

subroutine film (h, sink, temp, kstep, kinc, time, noel, npt, coords, jltyp, field, nfield, loadtype, node, area, vold, mi, ipkon, kon, lakon, iponoel, inoel, ielprop, prop, ielmat, shcon, nshcon, rhcon, nrhcon, ntmat_, cocon, ncocon, ipobody, xbody, ibody, heatnod, heatfac)
 

Function/Subroutine Documentation

◆ film()

subroutine film ( real*8, dimension(2), intent(out)  h,
real*8, intent(inout)  sink,
real*8, intent(in)  temp,
integer, intent(in)  kstep,
integer, intent(in)  kinc,
real*8, dimension(2), intent(in)  time,
integer, intent(in)  noel,
integer, intent(in)  npt,
real*8, dimension(3), intent(in)  coords,
integer, intent(in)  jltyp,
real*8, dimension(nfield), intent(in)  field,
integer, intent(in)  nfield,
character*20, intent(in)  loadtype,
integer, intent(in)  node,
real*8, intent(in)  area,
real*8, dimension(0:mi(2),*), intent(in)  vold,
integer, dimension(*), intent(in)  mi,
integer, dimension(*), intent(in)  ipkon,
integer, dimension(*), intent(in)  kon,
character*8, dimension(*), intent(in)  lakon,
integer, dimension(*), intent(in)  iponoel,
integer, dimension(2,*), intent(in)  inoel,
integer, dimension(*), intent(in)  ielprop,
real*8, dimension(*), intent(in)  prop,
integer, dimension(*), intent(in)  ielmat,
real*8, dimension(0:3,ntmat_,*), intent(in)  shcon,
integer, dimension(*), intent(in)  nshcon,
real*8, dimension(0:1,ntmat_,*), intent(in)  rhcon,
integer, dimension(*), intent(in)  nrhcon,
integer, intent(in)  ntmat_,
real*8, dimension(0:6,ntmat_,*)  cocon,
integer, dimension(2,*)  ncocon,
integer, dimension(2,*), intent(in)  ipobody,
real*8, dimension(7,*), intent(in)  xbody,
integer, dimension(3,*), intent(in)  ibody,
real*8, intent(out)  heatnod,
real*8, intent(out)  heatfac 
)
24 !
25 ! user subroutine film
26 !
27 !
28 ! INPUT:
29 !
30 ! sink most recent sink temperature
31 ! temp current temperature value
32 ! kstep step number
33 ! kinc increment number
34 ! time(1) current step time
35 ! time(2) current total time
36 ! noel element number
37 ! npt integration point number
38 ! coords(1..3) global coordinates of the integration point
39 ! jltyp loading face kode:
40 ! 11 = face 1
41 ! 12 = face 2
42 ! 13 = face 3
43 ! 14 = face 4
44 ! 15 = face 5
45 ! 16 = face 6
46 ! field currently not used
47 ! nfield currently not used (value = 1)
48 ! loadtype load type label
49 ! node network node (only for forced convection)
50 ! area area covered by the integration point
51 ! vold(0..4,1..nk) solution field in all nodes;
52 ! for structural nodes:
53 ! 0: temperature
54 ! 1: displacement in global x-direction
55 ! 2: displacement in global y-direction
56 ! 3: displacement in global z-direction
57 ! 4: static pressure
58 ! for network nodes
59 ! 0: total temperature (at end nodes)
60 ! = static temperature for liquids
61 ! 1: mass flow (at middle nodes)
62 ! 2: total pressure (at end nodes)
63 ! = static pressure for liquids
64 ! 3: static temperature (at end nodes; only for gas)
65 ! mi(1) max # of integration points per element (max
66 ! over all elements)
67 ! mi(2) max degree of freedom per node (max over all
68 ! nodes) in fields like v(0:mi(2))...
69 ! ipkon(i) points to the location in field kon preceding
70 ! the topology of element i
71 ! kon(*) contains the topology of all elements. The
72 ! topology of element i starts at kon(ipkon(i)+1)
73 ! and continues until all nodes are covered. The
74 ! number of nodes depends on the element label
75 ! lakon(i) contains the label of element i
76 ! iponoel(i) the network elements to which node i belongs
77 ! are stored in inoel(1,iponoel(i)),
78 ! inoel(1,inoel(2,iponoel(i)))...... until
79 ! inoel(2,inoel(2,inoel(2......)=0
80 ! inoel(1..2,*) field containing the network elements
81 ! ielprop(i) points to the location in field prop preceding
82 ! the properties of element i
83 ! prop(*) contains the properties of all network elements. The
84 ! properties of element i start at prop(ielprop(i)+1)
85 ! and continues until all properties are covered. The
86 ! appropriate amount of properties depends on the
87 ! element label. The kind of properties, their
88 ! number and their order corresponds
89 ! to the description in the user's manual,
90 ! cf. the sections "Fluid Section Types"
91 ! ielmat(i) contains the material number for element i
92 ! shcon(0,j,i) temperature at temperature point j of material i
93 ! shcon(1,j,i) specific heat at constant pressure at the
94 ! temperature point j of material i
95 ! shcon(2,j,i) dynamic viscosity at the temperature point j of
96 ! material i
97 ! shcon(3,1,i) specific gas constant of material i
98 ! nshcon(i) number of temperature data points for the specific
99 ! heat of material i
100 ! rhcon(0,j,i) temperature at density temperature point j of
101 ! material i
102 ! rhcon(1,j,i) density at the density temperature point j of
103 ! material i
104 ! nrhcon(i) number of temperature data points for the density
105 ! of material i
106 ! ntmat_ maximum number of temperature data points for
107 ! any material property for any material
108 ! ncocon(1,i) number of conductivity constants for material i
109 ! ncocon(2,i) number of temperature data points for the
110 ! conductivity coefficients of material i
111 ! cocon(0,j,i) temperature at conductivity temperature point
112 ! j of material i
113 ! cocon(k,j,i) conductivity coefficient k at conductivity
114 ! temperature point j of material i
115 ! ipobody(1,i) points to an entry in fields ibody and xbody
116 ! containing the body load applied to element i,
117 ! if any, else 0
118 ! ipobody(2,i) index referring to the line in field ipobody
119 ! containing a pointer to the next body load
120 ! applied to element i, else 0
121 ! ibody(1,i) code identifying the kind of body load i:
122 ! 1=centrifugal, 2=gravity, 3=generalized gravity
123 ! ibody(2,i) amplitude number for load i
124 ! ibody(3,i) load case number for load i
125 ! xbody(1,i) size of body load i
126 ! xbody(2..4,i) for centrifugal loading: point on the axis,
127 ! for gravity loading with known gravity vector:
128 ! normalized gravity vector
129 ! xbody(5..7,i) for centrifugal loading: normalized vector on the
130 ! rotation axis
131 !
132 ! OUTPUT:
133 !
134 ! h(1) magnitude of the film coefficient
135 ! h(2) not used; please do NOT assign any value
136 ! sink (updated) sink temperature (need not be
137 ! defined for forced convection)
138 ! heatnod extra heat flow going to the network node
139 ! (zero if not specified)
140 ! heatfac extra heat flow going to the structural face
141 ! (zero if not specified)
142 !
143  implicit none
144 !
145  character*8 lakon(*)
146  character*20 loadtype
147 !
148  integer kstep,kinc,noel,npt,jltyp,nfield,node,mi(*),ipkon(*),
149  & kon(*),iponoel(*),inoel(2,*),ielprop(*),ielmat(*),ntmat_,
150  & nshcon(*),nrhcon(*),ncocon(2,*),nodem,indexprop,indexe,
151  & iel1,iel2,ielup,iit,imat,icase,ithermal,ipobody(2,*),
152  & ibody(3,*)
153 !
154  real*8 h(2),sink,time(2),coords(3),temp,field(nfield),area,
155  & vold(0:mi(2),*),prop(*),shcon(0:3,ntmat_,*),rhcon(0:1,ntmat_,*),
156  & cocon(0:6,ntmat_,*),rho,r,pt,pr,xl,tt,ts,xflow,tsold,re,um,
157  & xks,xkappa,xlambda,f,cp,a,d,form_fact,xbody(7,*),heatnod,
158  & heatfac
159 !
160  intent(in) temp,kstep,kinc,time,noel,npt,
161  & coords,jltyp,field,nfield,loadtype,node,area,vold,mi,
162  & ipkon,kon,lakon,iponoel,inoel,ielprop,prop,ielmat,shcon,
163  & nshcon,rhcon,nrhcon,ntmat_,ipobody,ibody,xbody
164 !
165  intent(out) h,heatnod,heatfac
166 !
167  intent(inout) sink
168 !
169  if((node.eq.0).or.(iponoel(node).eq.0)) then
170 !
171 ! simple example: constant film coefficient
172 !
173  h(1)=200.d0
174  else
175 !
176 ! complicated example: forced convection with a film coefficient
177 ! determined by the Gnielinski equation (pipe application for
178 ! turbulent flow),
179 ! which runs like:
180 !
181 ! NuD=f/8*(ReD-1000)*pr/(1+12.7*sqrt(f/8)*(Pr**(2/3)-1))
182 !
183 ! NuD=h*D/xlambda: Nusselt number
184 ! ReD=massflow*D/(um*A): Reynolds number
185 ! Pr=um*cp/xlambda: Prandl number
186 ! h: film coefficient
187 ! D: hydraulic diameter
188 ! A: area of the pipe cross section
189 ! f: friction coefficient (cf. User's manual for formula)
190 ! xlambda: heat conduction coefficient
191 ! um: dynamic viscosity
192 ! cp: heat capacity
193 !
194 ! The convection node comes from the calling program: "node"
195 !
196 ! The elements connected to this node are determined by:
197 ! iel1=inoel(1,iponoel(node)),
198 ! iel2=inoel(1,inoel(2,iponoel(node))),
199 ! .... until
200 ! inoel(2,inoel(2,inoel(2,.......inoel(2,iponoel(node)))))=0
201 !
202 ! Let us assumed that "node" belongs to exactly two network
203 ! elements, i.e. inoel(2,inoel(2,iponoel(node)))=0
204 !
205 ! Let us look at the upstream element. To determine the
206 ! upstream element one looks at the sign of the mass flow
207 ! in the middle node of the elements.
208 !
209 ! The middle node nodem of element iel1 is given by
210 ! kon(ipkon(iel1)+2), the end nodes by
211 ! kon(ipkon(iel1)+1) and kon(ipkon(iel1)+3). The mass
212 ! flow in the element is given by vold(1,nodem). If this value
213 ! is positive and kon(ipkon(iel1)+3)=node or if is negative
214 ! and kon(ipkon(iel1)+1)=node iel1 is the upstream element
215 !
216 ! Let us assume this element is a gas pipe element, i.e.
217 ! lakon(iel1)='DGAPFA '. The properties of such an element
218 ! are the cross sectional area, the hydraulic diameter.... (in
219 ! that order), i.e. prop(ielprop(iel1)+1)=A,
220 ! prop(ielprop(iel1)+2)=D,...
221 !
222 ! The material number of element iel1 is given by ielmat(iel1)
223 ! with this information and the gas temperature (sink=Tfluid) the
224 ! gas material properties can be determined: xlambda by calling
225 ! materialdata_cond, um by calling materialdata_dvi and cp by
226 ! calling materialdata_cp
227 !
228 ! This yields all data needed to determine the film coefficient
229 ! with the Gnielinski equation
230 !
231 ! For laminar flow (Re < 3000) the following laminar flow
232 ! equation is used:
233 !
234 ! h=4.36*xlambda/D
235 !
236 ! elements belonging to the network node
237 !
238  iel1=inoel(1,iponoel(node))
239  if(inoel(2,iponoel(node)).ne.0) then
240  iel2=inoel(1,inoel(2,iponoel(node)))
241 !
242 ! check whether the node belongs to maximum two elements
243 !
244  if(inoel(2,inoel(2,iponoel(node))).ne.0) then
245  write(*,*) 'ERROR in film: the network node'
246  write(*,*) ' belongs to more than 2 elements'
247  call exit(201)
248  endif
249  else
250 !
251 ! node (must be an end node) belongs only to one
252 ! element (pure thermal network without entry or
253 ! exit element)
254 !
255  iel2=iel1
256  endif
257 !
258 ! only adiabatic gas pipes considered (heat exchange only
259 ! takes place at the end nodes, not within the pipe)
260 !
261  icase=0
262 !
263 ! check whether iel1 is the upstream element
264 !
265  indexe=ipkon(iel1)
266  nodem=kon(indexe+2)
267  if(((vold(1,nodem).ge.0.d0).and.(kon(indexe+3).eq.node)).or.
268  & ((vold(1,nodem).le.0.d0).and.(kon(indexe+1).eq.node))) then
269  ielup=iel1
270  else
271  ielup=iel2
272  endif
273 !
274 ! check whether the upstream element is an adiabatic gas
275 ! pipe element or a White-Colebrook liquid pipe
276 !
277  if((lakon(ielup)(1:6).ne.'DGAPFA').and.
278  & (lakon(ielup)(1:7).ne.'DLIPIWC')) then
279  write(*,*) 'ERROR in film: upstream element',ielup
280  write(*,*) ' is no adiabatic'
281  write(*,*) ' gas pipe nor White-Colebrook'
282  write(*,*) ' liquid pipe'
283  call exit(201)
284  endif
285 !
286  indexprop=ielprop(ielup)
287  a=prop(indexprop+1)
288  d=prop(indexprop+2)
289  xl=prop(indexprop+3)
290  xks=prop(indexprop+4)
291  form_fact=prop(indexprop+5)
292 !
293 ! material of upstream element
294 !
295  imat=ielmat(ielup)
296 !
297  xflow=dabs(vold(1,nodem))
298  tt=vold(0,node)
299  pt=vold(2,node)
300 !
301  if(lakon(ielup)(2:2).eq.'G') then
302 !
303 ! compressible flow
304 !
305  iit=0
306  ts=tt
307  do
308  iit=iit+1
309  tsold=ts
310  call materialdata_tg(imat,ntmat_,ts,shcon,nshcon,cp,r,
311  & um,rhcon,nrhcon,rho)
312  call ts_calc(xflow,tt,pt,xkappa,r,a,ts,icase)
313  if((dabs(ts-tsold).le.1.d-5*ts).or.(iit.eq.10)) exit
314  enddo
315 !
316  call materialdata_tg(imat,ntmat_,ts,shcon,nshcon,cp,r,
317  & um,rhcon,nrhcon,rho)
318  else
319 !
320 ! incompressible flow
321 !
322  ts=tt
323  call materialdata_cp(imat,ntmat_,ts,shcon,nshcon,cp)
324 !
325  ithermal=2
326  call materialdata_dvi(shcon,nshcon,imat,um,ts,ntmat_,
327  & ithermal)
328 !
329  endif
330 !
331  call materialdata_cond(imat,ntmat_,ts,cocon,ncocon,xlambda)
332 !
333  re=xflow*d/(um*a)
334 !
335  if(re.lt.3000.d0) then
336 !
337 ! laminar flow
338 !
339  h(1)=4.36d0*xlambda/d
340  else
341 !
342 ! turbulent flow
343 !
344  if(re.gt.5.e6) then
345  write(*,*) '*ERROR in film: Reynolds number ',re
346  write(*,*) ' is outside valid range'
347  call exit(201)
348  endif
349 !
350  pr=um*cp/xlambda
351 !
352  if((pr.lt.0.5d0).or.(pr.gt.2000.d0)) then
353  write(*,*) '*ERROR in film: Prandl number ',pr
354  write(*,*) ' is outside valid range'
355  call exit(201)
356  endif
357 !
358  call friction_coefficient(xl,d,xks,re,form_fact,f)
359 !
360  h(1)=f/8.d0*(re-1000.d0)*pr/
361  & (1.d0+12.7d0*dsqrt(f/8.d0)*(pr**(2.d0/3.d0)-1.d0))
362  & *xlambda/d
363  endif
364  endif
365 !
366  return
subroutine ts_calc(xflow, Tt, Pt, kappa, r, A, Ts, icase)
Definition: ts_calc.f:20
subroutine friction_coefficient(l, d, ks, reynolds, form_fact, lambda)
Definition: friction_coefficient.f:26
subroutine materialdata_cond(imat, ntmat_, t1l, cocon, ncocon, cond)
Definition: materialdata_cond.f:19
subroutine materialdata_tg(imat, ntmat_, t1l, shcon, nshcon, sph, r, dvi, rhcon, nrhcon, rho)
Definition: materialdata_tg.f:20
subroutine materialdata_cp(imat, ntmat_, t1l, shcon, nshcon, cp)
Definition: materialdata_cp.f:19
subroutine materialdata_dvi(shcon, nshcon, imat, dvi, t1l, ntmat_, ithermal)
Definition: materialdata_dvi.f:20
Hosted by OpenAircraft.com, (Michigan UAV, LLC)