Skip to content

Commit 5d531d8

Browse files
committed
Bug fix: Previously, the user could specify element normal and tangent vectors that make the spanwise vector (and element circulation) incorrectly oriented in the wake grid. Added code to reconcile the element spanwise vector direction with the wake grid spanwise direction.
1 parent c6e900e commit 5d531d8

File tree

3 files changed

+25
-5
lines changed

3 files changed

+25
-5
lines changed

mod/element.f95

+4-2
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,8 @@ MODULE element
5555
real, allocatable :: tzBC(:) ! Tangential Z for each blade segment
5656
real, allocatable :: sxBC(:) ! Spanwise X for each blade segment
5757
real, allocatable :: syBC(:) ! Spanwise Y for each blade segment
58-
real, allocatable :: szBC(:) ! Spanwise Z for each blade segment
58+
real, allocatable :: szBC(:) ! Spanwise Z for each blade segment
59+
real, allocatable :: CircSign(:) ! Direction of segment circulation on wake grid at positive lift
5960
real, allocatable :: eArea(:) ! Element area to radius ratio for each element
6061
real, allocatable :: eChord(:) ! Element chord to radius ratio for each element
6162
integer, allocatable :: iSect(:) ! Array of indicies of the section table to apply to each blade element
@@ -116,7 +117,8 @@ SUBROUTINE element_cns(MaxSegEnds,MaxSegEndPerBlade)
116117
allocate(tzBC(MaxSegEnds))
117118
allocate(sxBC(MaxSegEnds))
118119
allocate(syBC(MaxSegEnds))
119-
allocate(szBC(MaxSegEnds))
120+
allocate(szBC(MaxSegEnds))
121+
allocate(CircSign(MaxSegEnds))
120122
allocate(eArea(MaxSegEnds))
121123
allocate(eChord(MaxSegEnds))
122124
allocate(iSect(MaxSegEnds))

src/BGeomSetup.f95

+16-1
Original file line numberDiff line numberDiff line change
@@ -77,6 +77,11 @@ SUBROUTINE BGeomSetup()
7777
yBC(nej)=0.5*(Blades(i)%QCy(j)+Blades(i)%QCy(j+1))
7878
zBC(nej)=0.5*(Blades(i)%QCz(j)+Blades(i)%QCz(j+1))
7979

80+
! QC line
81+
dx=Blades(i)%QCx(j+1)-Blades(i)%QCx(j)
82+
dy=Blades(i)%QCy(j+1)-Blades(i)%QCy(j)
83+
dz=Blades(i)%QCz(j+1)-Blades(i)%QCz(j)
84+
8085
! Set element tangent vectors, txBC(MaxSegEnd)
8186
txBC(nej)=0.5*(Blades(i)%tx(j)+Blades(i)%tx(j+1))
8287
tyBC(nej)=0.5*(Blades(i)%ty(j)+Blades(i)%ty(j+1))
@@ -102,13 +107,23 @@ SUBROUTINE BGeomSetup()
102107
nyBC(nej)=nyBC(nej)/VMag
103108
nzBC(nej)=nzBC(nej)/VMag
104109

105-
! Calculate spanwise vector (s = t x n)
110+
! Calculate element spanwise vector (s = t x n)
106111
CALL cross(txBC(nej),tyBC(nej),tzBC(nej),nxBC(nej),nyBC(nej),nzBC(nej),sxBC(nej),syBC(nej),szBC(nej))
107112
! Force normalize
108113
VMag=sqrt(sxBC(nej)**2+syBC(nej)**2+szBC(nej)**2)
109114
sxBC(nej)=sxBC(nej)/VMag
110115
syBC(nej)=syBC(nej)/VMag
111116
szBC(nej)=szBC(nej)/VMag
117+
! Calc projection direction of element spanwise vector on QC line.
118+
! Used to correctly orient circulation in wake grid.
119+
! Note pos. lift creates circulation in neg. element spanwise direction
120+
dp=sxBC(nej)*dx+syBC(nej)*dy+szBC(nej)*dz
121+
if (dp>0) then
122+
CircSign(nej)=-1.0
123+
else
124+
CircSign(nej)=1.0
125+
end if
126+
112127

113128
end do
114129

src/bsload.f95

+5-2
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ SUBROUTINE bsload(nElem,IsBE,alpha,Re,umach,ur,CN,CT,Fx,Fy,Fz,te)
2020
real uAve, vAve, wAve, uFSAve, vFSAve, wFSAve, uBlade, vBlade, wBlade, urdn, urdc
2121
real xe5, ye5, ze5, xe75, ye75, ze75, uBlade5, vBlade5, wBlade5, uBlade75, vBlade75, wBlade75
2222
real urdn5, ur5, alpha5, Re5, urdn75, ur75, alpha75, Re75
23-
real CL, CD, CM25, FN, FT, MS, TRx, TRy, TRz, CLCirc
23+
real CL, CD, CM25, FN, FT, MS, TRx, TRy, TRz, CLCirc, CircDir
2424

2525

2626
! Calculates aero loads on a blade element. Static and dynamic airfoil characteristics calculated here...
@@ -50,6 +50,9 @@ SUBROUTINE bsload(nElem,IsBE,alpha,Re,umach,ur,CN,CT,Fx,Fy,Fz,te)
5050
sye=syBC(nElem)
5151
sze=szBC(nElem)
5252

53+
! Direction of circulation in wake grid at positive lift
54+
CircDir=CircSign(nElem)
55+
5356
! Airfoil section
5457
SectInd=isect(nElem)
5558

@@ -114,7 +117,7 @@ SUBROUTINE bsload(nElem,IsBE,alpha,Re,umach,ur,CN,CT,Fx,Fy,Fz,te)
114117

115118
! Bound vortex strength from CL via Kutta-Joukowski analogy.
116119
! Save corresponding AOA as well
117-
GB(nElem1)=CLCirc*ElemChordR*ur/2.0
120+
GB(nElem1)=CircDir*(CLCirc*ElemChordR*ur/2.0)
118121
AOA(nElem1)=alpha
119122
! normalized time step used to update states in the LB model
120123
ds(nElem)=2.0*ur*DT/ElemChordR

0 commit comments

Comments
 (0)