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

Go to the source code of this file.

Functions/Subroutines

subroutine mafilltcomp (nef, ipnei, neifa, neiel, vfa, xxn, area, au, ad, jq, irow, nzs, b, vel, umel, xlet, xle, gradtfa, xxi, body, volume, ielfa, lakonf, ifabou, nbody, neq, dtimef, velo, veloo, cvfa, hcfa, cvel, gradvel, xload, gamma, xrlfa, xxj, nactdohinv, a1, a2, a3, flux, nefa, nefb, iau6, xxni, xxnj)
 

Function/Subroutine Documentation

◆ mafilltcomp()

subroutine mafilltcomp ( integer, intent(in)  nef,
integer, dimension(*), intent(in)  ipnei,
integer, dimension(*), intent(in)  neifa,
integer, dimension(*), intent(in)  neiel,
real*8, dimension(0:7,*), intent(in)  vfa,
real*8, dimension(3,*), intent(in)  xxn,
real*8, dimension(*), intent(in)  area,
real*8, dimension(*), intent(inout)  au,
real*8, dimension(*), intent(inout)  ad,
integer, dimension(*), intent(in)  jq,
integer, dimension(*), intent(in)  irow,
integer, intent(in)  nzs,
real*8, dimension(neq), intent(inout)  b,
real*8, dimension(nef,0:7), intent(in)  vel,
real*8, dimension(*), intent(in)  umel,
real*8, dimension(*), intent(in)  xlet,
real*8, dimension(*), intent(in)  xle,
real*8, dimension(3,*), intent(in)  gradtfa,
real*8, dimension(3,*), intent(in)  xxi,
real*8, dimension(0:3,*), intent(in)  body,
real*8, dimension(*), intent(in)  volume,
integer, dimension(4,*), intent(in)  ielfa,
character*8, dimension(*), intent(in)  lakonf,
integer, dimension(*), intent(in)  ifabou,
integer, intent(in)  nbody,
integer, intent(in)  neq,
real*8, intent(in)  dtimef,
real*8, dimension(nef,0:7), intent(in)  velo,
real*8, dimension(nef,0:7), intent(in)  veloo,
real*8, dimension(*), intent(in)  cvfa,
real*8, dimension(*), intent(in)  hcfa,
real*8, dimension(*), intent(in)  cvel,
real*8, dimension(3,3,*), intent(in)  gradvel,
real*8, dimension(2,*), intent(in)  xload,
real*8, dimension(*), intent(in)  gamma,
real*8, dimension(3,*), intent(in)  xrlfa,
real*8, dimension(3,*), intent(in)  xxj,
integer, dimension(*), intent(in)  nactdohinv,
real*8, intent(in)  a1,
real*8, intent(in)  a2,
real*8, intent(in)  a3,
real*8, dimension(*), intent(in)  flux,
integer, intent(in)  nefa,
integer, intent(in)  nefb,
integer, dimension(6,*)  iau6,
real*8, dimension(3,*)  xxni,
real*8, dimension(3,*)  xxnj 
)
24 !
25 ! filling the matrix for the conservation of energy
26 !
27  implicit none
28 !
29  logical knownflux
30 !
31  character*8 lakonf(*)
32 !
33  integer i,nef,indexf,ipnei(*),j,ifa,iel,neifa(*),
34  & neiel(*),jdof2,jq(*),irow(*),nzs,ielfa(4,*),iau6(6,*),
35  & ipointer,ifabou(*),nbody,neq,indexb,nactdohinv(*),
36  & nefa,nefb
37 !
38  real*8 xflux,vfa(0:7,*),xxn(3,*),area(*),au(*),ad(*),b(neq),
39  & vel(nef,0:7),umel(*),xlet(*),xle(*),coef,gradtfa(3,*),
40  & xxi(3,*),body(0:3,*),volume(*),dtimef,velo(nef,0:7),
41  & veloo(nef,0:7),rhovel,constant,cvel(*),gradvel(3,3,*),
42  & cvfa(*),hcfa(*),div,xload(2,*),gamma(*),xrlfa(3,*),
43  & xxj(3,*),a1,a2,a3,flux(*),xxni(3,*),xxnj(3,*)
44 !
45  intent(in) nef,ipnei,neifa,neiel,vfa,xxn,area,
46  & jq,irow,nzs,vel,umel,xlet,xle,gradtfa,xxi,
47  & body,volume,ielfa,lakonf,ifabou,nbody,neq,
48  & dtimef,velo,veloo,cvfa,hcfa,cvel,gradvel,xload,gamma,xrlfa,
49  & xxj,nactdohinv,a1,a2,a3,flux,nefa,nefb
50 !
51  intent(inout) au,ad,b
52 !
53  do i=nefa,nefb
54  do indexf=ipnei(i)+1,ipnei(i+1)
55 !
56 ! convection
57 !
58  ifa=neifa(indexf)
59  iel=neiel(indexf)
60  xflux=flux(indexf)*cvfa(ifa)
61 !
62  if(xflux.ge.0.d0) then
63 !
64 ! outflowing flux
65 !
66  ad(i)=ad(i)+xflux
67 ! centdiff
68 c b(i)=b(i)-gamma(ifa)*(vfa(0,ifa)-vel(i,0))*xflux
69 !end centdiff
70  else
71  if(iel.gt.0) then
72 !
73 ! incoming flux from neighboring element
74 !
75  au(indexf)=au(indexf)+xflux
76 !centdiff
77 c b(i)=b(i)-gamma(ifa)*(vfa(0,ifa)-vel(iel,0))*xflux
78 !end centdiff
79  else
80 !
81 ! incoming flux through boundary
82 !
83  if(ielfa(2,ifa).lt.0) then
84  indexb=-ielfa(2,ifa)
85  if((ifabou(indexb).ne.0).or.
86  & (dabs(xflux).lt.1.d-10)) then
87  b(i)=b(i)-vfa(0,ifa)*xflux
88  else
89 c write(*,*) '*ERROR in mafillt: the tempera-'
90 c write(*,*) ' ture of an incoming flux'
91 c write(*,*) ' through face ',j,'of'
92 c write(*,*)' element ',nactdohinv(i),
93 c & ' is not given'
94  endif
95  else
96 c write(*,*) '*ERROR in mafillt: the tempera-'
97 c write(*,*) ' ture of an incoming flux'
98 c write(*,*) ' through face ',j,'of'
99 c write(*,*)' element ',nactdohinv(i),
100 c & ' is not given'
101  endif
102  endif
103  endif
104 !
105 ! diffusion
106 !
107  if(iel.ne.0) then
108 !
109 ! neighboring element
110 !
111  coef=hcfa(ifa)*area(ifa)/xlet(indexf)
112  ad(i)=ad(i)+coef
113  au(indexf)=au(indexf)-coef
114 !
115 ! correction for non-orthogonal grid
116 !
117  b(i)=b(i)+hcfa(ifa)*area(ifa)*
118  & (gradtfa(1,ifa)*xxnj(1,indexf)+
119  & gradtfa(2,ifa)*xxnj(2,indexf)+
120  & gradtfa(3,ifa)*xxnj(3,indexf))
121  else
122 !
123 ! boundary; either temperature given or adiabatic
124 ! or outlet
125 !
126  knownflux=.false.
127  ipointer=abs(ielfa(2,ifa))
128  if(ipointer.gt.0) then
129  if(ifabou(ipointer+6).gt.0) then
130 !
131 ! heat flux is known
132 !
133  b(i)=b(i)-xload(1,ifabou(ipointer+6))
134  knownflux=.true.
135 !
136  elseif((ifabou(ipointer).ne.0).or.
137  & (ifabou(ipointer+1).ne.0).or.
138  & (ifabou(ipointer+2).ne.0).or.
139  & (ifabou(ipointer+3).ne.0)) then
140 !
141 ! temperature given or no outlet:
142 ! temperature is assumed fixed
143 !
144  coef=hcfa(ifa)*area(ifa)/xle(indexf)
145  ad(i)=ad(i)+coef
146  b(i)=b(i)+coef*vfa(0,ifa)
147  else
148 !
149 ! outlet: no diffusion
150 !
151  endif
152  endif
153 !
154 ! correction for non-orthogonal grid
155 !
156  if(.not.knownflux) then
157  b(i)=b(i)+hcfa(ifa)*area(ifa)*
158  & (gradtfa(1,ifa)*xxni(1,indexf)+
159  & gradtfa(2,ifa)*xxni(2,indexf)+
160  & gradtfa(3,ifa)*xxni(3,indexf))
161  endif
162  endif
163  enddo
164 !
165 ! -p*div(v) term
166 !
167  div=gradvel(1,1,i)+gradvel(2,2,i)+gradvel(3,3,i)
168  b(i)=b(i)-vel(i,4)*div*volume(i)
169 !
170 ! viscous dissipation
171 !
172  b(i)=b(i)+umel(i)*volume(i)*
173  & (2.d0*(gradvel(1,1,i)**2+gradvel(2,2,i)**2+
174  & gradvel(3,3,i)**2)+
175  & (gradvel(1,2,i)+gradvel(2,1,i))**2+
176  & (gradvel(1,3,i)+gradvel(3,1,i))**2+
177  & (gradvel(2,3,i)+gradvel(3,2,i))**2)
178  b(i)=b(i)-2.d0*umel(i)*volume(i)/3.d0*div**2
179 !
180 ! body heat source and body sources
181 !
182  rhovel=vel(i,5)*volume(i)
183 !
184  if(nbody.gt.0) then
185  b(i)=b(i)+rhovel*body(0,i)
186  endif
187 !
188 ! transient term
189 !
190 c a1=1.d0/dtimef
191 c a2=-1.d0/dtimef
192 c a3=0.d0/dtimef
193 c constant=rhovel*cvel(i)
194 c b(i)=b(i)-(a2*velo(i,0)+a3*veloo(i,0))*constant
195 c
196  constant=rhovel*cvel(i)/dtimef
197  b(i)=b(i)+velo(i,0)*constant
198  ad(i)=ad(i)+constant
199 !
200  enddo
201 !
202  return
subroutine flux(node1, node2, nodem, nelem, lakon, kon, ipkon, nactdog, identity, ielprop, prop, kflag, v, xflow, f, nodef, idirf, df, cp, R, rho, physcon, g, co, dvi, numf, vold, set, shcon, nshcon, rhcon, nrhcon, ntmat_, mi, ider, ttime, time, iaxial)
Definition: flux.f:24
Hosted by OpenAircraft.com, (Michigan UAV, LLC)