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

Go to the source code of this file.

Functions/Subroutines

subroutine correctvfa (nface, ielfa, area, vfa, ap, bp, xxn, ifabou, ipnei, nef, neifa, hfa, vel, xboun, lakonf, flux)
 

Function/Subroutine Documentation

◆ correctvfa()

subroutine correctvfa ( integer  nface,
integer, dimension(4,*)  ielfa,
real*8, dimension(*)  area,
real*8, dimension(0:7,*)  vfa,
real*8, dimension(*)  ap,
real*8, dimension(*)  bp,
real*8, dimension(3,*)  xxn,
integer, dimension(*)  ifabou,
integer, dimension(*)  ipnei,
integer  nef,
integer, dimension(*)  neifa,
real*8, dimension(3,*)  hfa,
real*8, dimension(nef,0:7)  vel,
real*8, dimension(*)  xboun,
character*8, dimension(*)  lakonf,
real*8, dimension(*)  flux 
)
21 !
22 ! correction of v due to the balance of mass
23 ! the correction is in normal direction to the face
24 !
25  implicit none
26 !
27  character*8 lakonf(*)
28 !
29  integer i,nface,ielfa(4,*),iel1,iel2,ifabou(*),j,indexf,k,
30  & ipnei(*),ifa,nef,neifa(*),indexb
31 !
32  real*8 ap(*),bp(*),area(*),vfa(0:7,*),xxn(3,*),flux(*),
33  & hfa(3,*),vel(nef,0:7),dh,xboun(*),totflux
34 !
35 c$omp parallel default(none)
36 c$omp& shared(nface,ielfa,ipnei,area,ap,vfa,hfa,xxn,vel,bp,ifabou,xboun)
37 c$omp& private(i,iel1,j,indexf,iel2,dh,k,indexb)
38 c$omp do
39  do i=1,nface
40 !
41 ! first neighboring element
42 !
43  iel1=ielfa(1,i)
44  j=ielfa(4,i)
45  indexf=ipnei(iel1)+j
46 !
47 ! second neighboring element
48 !
49  iel2=ielfa(2,i)
50 !
51 ! factor between mass flow and velocity
52 !
53  ap(i)=ap(i)/(area(i)*vfa(5,i))
54 !
55 ! internal face
56 !
57  if(iel2.gt.0) then
58  dh=hfa(1,i)*xxn(1,indexf)+
59  & hfa(2,i)*xxn(2,indexf)+
60  & hfa(3,i)*xxn(3,indexf)
61  do k=1,3
62 !
63 ! bp applies if the neighbor element has a higher
64 ! number than the observer element, else a negative
65 ! sign has to be appended
66 !
67  if(iel1.lt.iel2) then
68  vfa(k,i)=(dh-ap(i)*(vel(iel2,4)-vel(iel1,4)+bp(i)))
69  & *xxn(k,indexf)
70  else
71  vfa(k,i)=(dh-ap(i)*(vel(iel2,4)-vel(iel1,4)-bp(i)))
72  & *xxn(k,indexf)
73  endif
74  enddo
75 !
76  elseif(iel2.lt.0) then
77 !
78 ! if flux given: no correction (important for compressible
79 ! flows in which flux and pressure can be given for the
80 ! same face)
81 !
82  if(((ifabou(-iel2+1).eq.0).or.
83  & (ifabou(-iel2+2).eq.0).or.
84  & (ifabou(-iel2+3).eq.0)).and.
85  & (ifabou(-iel2+5).eq.0)) then
86  indexb=ifabou(-iel2+4)
87  if(indexb.ne.0) then
88 !
89 ! external face with pressure boundary condition
90 !
91  dh=hfa(1,i)*xxn(1,indexf)+
92  & hfa(2,i)*xxn(2,indexf)+
93  & hfa(3,i)*xxn(3,indexf)
94  do k=1,3
95  vfa(k,i)=(dh-ap(i)*
96  & (xboun(indexb)-vel(iel1,4)+bp(i)))
97  & *xxn(k,indexf)
98  enddo
99  endif
100  endif
101  endif
102  enddo
103 c$omp end do
104 c$omp end parallel
105 !
106 ! check conservation of mass
107 !
108 c$omp parallel default(none)
109 c$omp& shared(nef,ipnei,lakonf,neifa,ielfa,ifabou,flux,area,vfa,xxn)
110 c$omp& private(i,totflux,indexf,j,ifa)
111 c$omp do
112  do i=1,nef
113 c totflux=0.d0
114 c indexf=ipnei(i)
115 c do j=1,ipnei(i+1)-ipnei(i)
116 c indexf=indexf+1
117  do indexf=ipnei(i)+1,ipnei(i+1)
118  ifa=neifa(indexf)
119 !
120  if(ielfa(2,ifa).lt.0) then
121  if(ifabou(-ielfa(2,ifa)+5).lt.0) then
122  flux(indexf)=0.d0
123  cycle
124  endif
125  endif
126 !
127  flux(indexf)=area(ifa)*vfa(5,ifa)*
128  & (vfa(1,ifa)*xxn(1,indexf)+
129  & vfa(2,ifa)*xxn(2,indexf)+
130  & vfa(3,ifa)*xxn(3,indexf))
131 c write(*,*) 'correctvfa ',i,ifa
132 c write(*,*) vfa(5,ifa)
133 c write(*,*) vfa(1,ifa)
134 c write(*,*) vfa(2,ifa)
135 c write(*,*) vfa(3,ifa)
136 c write(*,*) flux(ifa)
137 c totflux=totflux+flux(indexf)
138  enddo
139 c write(*,*) 'correctvfa mass check ',i,totflux
140  enddo
141 c$omp end do
142 c$omp end parallel
143 c write(*,*)
144 !
145  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)