Skip to content

Commit f7d5609

Browse files
author
ghaymanNREL
authored
Revert "Pull branch (#18)"
This reverts commit 055be86.
1 parent 055be86 commit f7d5609

10 files changed

+454
-733
lines changed

modules-local/aerodyn/src/AeroDyn.f90

+8-27
Original file line numberDiff line numberDiff line change
@@ -866,8 +866,7 @@ subroutine SetParameters( InitInp, InputFileData, p, ErrStat, ErrMsg )
866866

867867
p%AirDens = InputFileData%AirDens
868868
p%KinVisc = InputFileData%KinVisc
869-
870-
869+
p%SpdSound = InputFileData%SpdSound
871870

872871
!p%AFI ! set in call to AFI_Init() [called early because it wants to use the same echo file as AD]
873872
!p%BEMT ! set in call to BEMT_Init()
@@ -1418,11 +1417,7 @@ SUBROUTINE ValidateInputData( InitInp, InputFileData, NumBl, ErrStat, ErrMsg )
14181417
if (InputFileData%AirDens <= 0.0) call SetErrStat ( ErrID_Fatal, 'The air density (AirDens) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
14191418
if (InputFileData%KinVisc <= 0.0) call SetErrStat ( ErrID_Fatal, 'The kinesmatic viscosity (KinVisc) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
14201419
if (InputFileData%SpdSound <= 0.0) call SetErrStat ( ErrID_Fatal, 'The speed of sound (SpdSound) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
1421-
if (InputFileData%Pvap <= 0.0) call SetErrStat ( ErrID_Fatal, 'The vapour pressure (Pvap) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
1422-
if (InputFileData%Patm <= 0.0) call SetErrStat ( ErrID_Fatal, 'The atmospheric pressure (Patm) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
1423-
if (InputFileData%FluidDepth <= 0.0) call SetErrStat ( ErrID_Fatal, 'Fluid depth (FluidDepth) cannot be negative', ErrStat, ErrMsg, RoutineName )
1424-
1425-
1420+
14261421

14271422
! BEMT inputs
14281423
! bjj: these checks should probably go into BEMT where they are used...
@@ -1444,14 +1439,7 @@ SUBROUTINE ValidateInputData( InitInp, InputFileData, NumBl, ErrStat, ErrMsg )
14441439

14451440
if (.not. InputFileData%FLookUp ) call SetErrStat( ErrID_Fatal, 'FLookUp must be TRUE for this version.', ErrStat, ErrMsg, RoutineName )
14461441
end if
1447-
1448-
if ( InputFileData%CavitCheck .and. InputFileData%AFAeroMod == 2) then
1449-
call SetErrStat( ErrID_Fatal, 'Cannot use unsteady aerodynamics module with a cavitation check', ErrStat, ErrMsg, RoutineName )
1450-
end if
1451-
1452-
if (InputFileData%InCol_Cpmin == 0 .and. InputFileData%CavitCheck) call SetErrStat( ErrID_Fatal, 'InCol_Cpmin must not be 0 to do a cavitation check.', ErrStat, ErrMsg, RoutineName )
1453-
1454-
1442+
14551443

14561444
! validate the AFI input data because it doesn't appear to be done in AFI
14571445
if (InputFileData%NumAFfiles < 1) call SetErrStat( ErrID_Fatal, 'The number of unique airfoil tables (NumAFfiles) must be greater than zero.', ErrStat, ErrMsg, RoutineName )
@@ -1711,10 +1699,7 @@ SUBROUTINE Init_BEMTmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, y,
17111699
InitInp%numBlades = p%NumBlades
17121700

17131701
InitInp%airDens = InputFileData%AirDens
1714-
InitInp%kinVisc = InputFileData%KinVisc
1715-
InitInp%Patm = InputFileData%Patm
1716-
InitInp%Pvap = InputFileData%Pvap
1717-
InitInp%FluidDepth = InputFileData%FluidDepth
1702+
InitInp%kinVisc = InputFileData%KinVisc
17181703
InitInp%skewWakeMod = InputFileData%SkewMod
17191704
InitInp%aTol = InputFileData%IndToler
17201705
InitInp%useTipLoss = InputFileData%TipLoss
@@ -1763,13 +1748,10 @@ SUBROUTINE Init_BEMTmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, y,
17631748
end do
17641749
end do
17651750

1766-
InitInp%UA_Flag = InputFileData%AFAeroMod == AFAeroMod_BL_unsteady
1767-
InitInp%UAMod = InputFileData%UAMod
1768-
InitInp%Flookup = InputFileData%Flookup
1769-
InitInp%a_s = InputFileData%SpdSound
1770-
InitInp%CavitCheck = InputFileData%CavitCheck
1771-
1772-
1751+
InitInp%UA_Flag = InputFileData%AFAeroMod == AFAeroMod_BL_unsteady
1752+
InitInp%UAMod = InputFileData%UAMod
1753+
InitInp%Flookup = InputFileData%Flookup
1754+
InitInp%a_s = InputFileData%SpdSound
17731755

17741756
if (ErrStat >= AbortErrLev) then
17751757
call cleanup()
@@ -3775,7 +3757,6 @@ FUNCTION CheckBEMTInputPerturbations( p, m ) RESULT(ValidPerturb)
37753757

37763758
end if
37773759

3778-
37793760
else ! not UseInduction
37803761

37813762
do k=1,p%NumBlades

modules-local/aerodyn/src/AeroDyn_Driver.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -197,4 +197,4 @@ subroutine Dvr_End()
197197
end subroutine Dvr_End
198198
!................................
199199
end program AeroDyn_Driver
200-
200+

modules-local/aerodyn/src/AeroDyn_IO.f90

+423-595
Large diffs are not rendered by default.

modules-local/aerodyn/src/AeroDyn_Registry.txt

-4
Original file line numberDiff line numberDiff line change
@@ -65,12 +65,8 @@ typedef ^ AD_InputFile IntKi TwrPotent - - - "Type tower influence on wind based
6565
typedef ^ AD_InputFile LOGICAL TwrShadow - - - "Calculate tower influence on wind based on downstream tower shadow?" -
6666
typedef ^ AD_InputFile LOGICAL TwrAero - - - "Calculate tower aerodynamic loads?" flag
6767
typedef ^ AD_InputFile Logical FrozenWake - - - "Flag that tells this module it should assume a frozen wake during linearization." -
68-
typedef ^ AD_InputFile Logical CavitCheck - - - "Flag that tells us if we want to check for cavitation" -
6968
typedef ^ AD_InputFile ReKi AirDens - - - "Air density" kg/m^3
7069
typedef ^ AD_InputFile ReKi KinVisc - - - "Kinematic air viscosity" m^2/s
71-
typedef ^ AD_InputFile ReKi Patm - - - "Atmospheric pressure" Pa
72-
typedef ^ AD_InputFile ReKi Pvap - - - "Vapour pressure" Pa
73-
typedef ^ AD_InputFile ReKi FluidDepth - - - "Submerged hub depth" m
7470
typedef ^ AD_InputFile ReKi SpdSound - - - "Speed of sound" m/s
7571
typedef ^ AD_InputFile IntKi SkewMod - - - "Type of skewed-wake correction model {1=uncoupled, 2=Pitt/Peters, 3=coupled} [used only when WakeMod=1]" -
7672
typedef ^ AD_InputFile LOGICAL TipLoss - - - "Use the Prandtl tip-loss model? [used only when WakeMod=1]" flag

modules-local/aerodyn/src/AirfoilInfo.f90

+1-8
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,6 @@ SUBROUTINE AFI_Init ( InitInput, p, ErrStat, ErrMsg, UnEcho )
110110
p%ColCd = 2
111111
p%ColCm = 0 ! These may or may not be used; initialize to zero in case they aren't used
112112
p%ColCpmin = 0 ! These may or may not be used; initialize to zero in case they aren't used
113-
114113
IF ( InitInput%InCol_Cm > 0 ) THEN
115114
p%ColCm = 3
116115
IF ( InitInput%InCol_Cpmin > 0 ) THEN
@@ -120,8 +119,8 @@ SUBROUTINE AFI_Init ( InitInput, p, ErrStat, ErrMsg, UnEcho )
120119
p%ColCpmin = 3
121120
END IF
122121
NumCoefs = MAX(p%ColCd, p%ColCm,p%ColCpmin) ! number of non-zero coefficient columns
122+
123123

124-
125124
! Process the airfoil files.
126125

127126
ALLOCATE ( p%AFInfo( InitInput%NumAFfiles ), STAT=ErrStat2 )
@@ -130,9 +129,6 @@ SUBROUTINE AFI_Init ( InitInput, p, ErrStat, ErrMsg, UnEcho )
130129
RETURN
131130
ENDIF
132131

133-
p%AFInfo( :)%ColCpmin=p%ColCpmin
134-
p%AFInfo( :)%ColCm=p%ColCm
135-
136132

137133
DO File=1,InitInput%NumAFfiles
138134

@@ -500,7 +496,6 @@ SUBROUTINE ReadAFfile ( AFfile, NumCoefs, InCol_Alfa, InCol_Cl, InCol_Cd, InCol_
500496
TYPE (AFInfoType), INTENT(INOUT) :: AFInfo ! The derived type for holding the constant parameters for this airfoil.
501497

502498

503-
504499
! Local declarations.
505500

506501
REAL(ReKi) :: Coords (2) ! An array to hold data from the airfoil-shape table.
@@ -810,8 +805,6 @@ SUBROUTINE ReadAFfile ( AFfile, NumCoefs, InCol_Alfa, InCol_Cl, InCol_Cd, InCol_
810805
CALL Cleanup()
811806
RETURN
812807
ENDIF
813-
814-
815808

816809
DO Row=1,AFInfo%Table(Table)%NumAlf
817810

modules-local/aerodyn/src/AirfoilInfo_Registry.txt

-2
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,6 @@ typedef ^ ^ INTEGER NumCpminAoAkts - - - "The number of angle-of-attack knots fo
9494
typedef ^ ^ INTEGER NumCpminReKts - - - "The number of log(Re) knots for 2D splines of Cpmin" -
9595
typedef ^ ^ INTEGER NumTabs - - - "The number of airfoil tables in the airfoil file" -
9696
typedef ^ ^ AFI_Table_Type Table {:} - - "The tables of airfoil data for given Re and control setting" -
97-
typedef ^ ^ INTEGER ColCpmin - - - "Column number for Cpmin" -
98-
typedef ^ ^ INTEGER ColCm - - - "Column number for Cm" -
9997

10098
# ..... Initialization data .......................................................................................................
10199
# The following derived type stores information that comes from the calling module (say, AeroDyn):

modules-local/aerodyn/src/BEMT.f90

+11-62
Original file line numberDiff line numberDiff line change
@@ -162,9 +162,6 @@ subroutine BEMT_SetParameters( InitInp, p, errStat, errMsg )
162162
p%numBladeNodes = InitInp%numBladeNodes
163163
p%numBlades = InitInp%numBlades
164164
p%UA_Flag = InitInp%UA_Flag
165-
p%CavitCheck = InitInp%CavitCheck
166-
167-
168165

169166
allocate ( p%chord(p%numBladeNodes, p%numBlades), STAT = errStat2 )
170167
if ( errStat2 /= 0 ) then
@@ -208,13 +205,10 @@ subroutine BEMT_SetParameters( InitInp, p, errStat, errMsg )
208205
end do
209206
end do
210207

211-
212-
!p%DT = InitInp%DT
208+
209+
!p%DT = InitInp%DT
213210
p%airDens = InitInp%airDens
214-
p%kinVisc = InitInp%kinVisc
215-
p%Patm = InitInp%Patm
216-
p%Pvap = InitInp%Pvap
217-
p%FluidDepth = InitInp%FluidDepth
211+
p%kinVisc = InitInp%kinVisc
218212
p%skewWakeMod = InitInp%skewWakeMod
219213
p%useTipLoss = InitInp%useTipLoss
220214
p%useHubLoss = InitInp%useHubLoss
@@ -225,7 +219,6 @@ subroutine BEMT_SetParameters( InitInp, p, errStat, errMsg )
225219
p%numReIterations = InitInp%numReIterations
226220
p%maxIndIterations = InitInp%maxIndIterations
227221
p%aTol = InitInp%aTol
228-
229222

230223
end subroutine BEMT_SetParameters
231224

@@ -438,15 +431,14 @@ end subroutine BEMT_AllocInput
438431

439432

440433
!----------------------------------------------------------------------------------------------------------------------------------
441-
subroutine BEMT_AllocOutput( y, p, m, errStat, errMsg )
434+
subroutine BEMT_AllocOutput( y, p, errStat, errMsg )
442435
! This routine is called from BEMT_Init.
443436
!
444437
!
445438
!..................................................................................................................................
446439

447440
type(BEMT_OutputType), intent( out) :: y ! output data
448441
type(BEMT_ParameterType), intent(in ) :: p ! Parameters
449-
type(BEMT_MiscVarType), intent(inout) :: m ! Misc/optimization variables
450442
integer(IntKi), intent( out) :: errStat ! Error status of the operation
451443
character(*), intent( out) :: errMsg ! Error message if ErrStat /= ErrID_None
452444

@@ -473,10 +465,6 @@ subroutine BEMT_AllocOutput( y, p, m, errStat, errMsg )
473465
call allocAry( y%Cm, p%numBladeNodes, p%numBlades, 'y%Cm', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
474466
call allocAry( y%Cl, p%numBladeNodes, p%numBlades, 'y%Cl', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
475467
call allocAry( y%Cd, p%numBladeNodes, p%numBlades, 'y%Cd', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
476-
call allocAry( m%Cpmin, p%numBladeNodes, p%numBlades, 'm%Cpmin', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
477-
call allocAry( m%SigmaCavit, p%numBladeNodes, p%numBlades, 'm%SigmaCavit', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
478-
call allocAry( m%SigmaCavitCrit, p%numBladeNodes, p%numBlades, 'm%SigmaCavitCrit', errStat2, errMsg2); call setErrStat(errStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
479-
480468

481469
if (ErrStat >= AbortErrLev) RETURN
482470

@@ -494,8 +482,7 @@ subroutine BEMT_AllocOutput( y, p, m, errStat, errMsg )
494482
y%tanInduction = 0.0_ReKi
495483
y%AOA = 0.0_ReKi
496484
y%Cl = 0.0_ReKi
497-
y%Cd = 0.0_ReKi
498-
485+
y%Cd = 0.0_ReKi
499486

500487
end subroutine BEMT_AllocOutput
501488

@@ -718,7 +705,6 @@ subroutine BEMT_Init( InitInp, u, p, x, xd, z, OtherState, AFInfo, y, misc, Inte
718705
write (69,'(A)') ' '
719706

720707
#endif
721-
722708

723709
do j = 1,p%numBlades
724710
do i = 1,p%numBladeNodes ! Loop over blades and nodes
@@ -740,8 +726,6 @@ subroutine BEMT_Init( InitInp, u, p, x, xd, z, OtherState, AFInfo, y, misc, Inte
740726
call WrScr( 'Warning: Turning off Unsteady Aerodynamics because C_nalpha is 0. BladeNode = '//trim(num2lstr(i))//', Blade = '//trim(num2lstr(j)) )
741727
end if
742728

743-
744-
745729
end do
746730
end do
747731

@@ -772,7 +756,7 @@ subroutine BEMT_Init( InitInp, u, p, x, xd, z, OtherState, AFInfo, y, misc, Inte
772756
!call BEMT_InitOut(p, InitOut, errStat2, errMsg2)
773757
!call CheckError( errStat2, errMsg2 )
774758

775-
call BEMT_AllocOutput(y, p, misc, errStat2, errMsg2) !u is sent so we can create sibling meshes
759+
call BEMT_AllocOutput(y, p, errStat2, errMsg2) !u is sent so we can create sibling meshes
776760
call SetErrStat( errStat2, errMsg2, errStat, errMsg, RoutineName )
777761
if (errStat >= AbortErrLev) then
778762
call cleanup()
@@ -1097,8 +1081,8 @@ subroutine BEMT_CalcOutput( t, u, p, x, xd, z, OtherState, AFInfo, y, m, errStat
10971081
! Local variables:
10981082

10991083

1100-
real(ReKi) :: Re, fzero, theta, Vx, Vy
1101-
real(ReKi) :: Rtip, SigmaCavitCrit, SigmaCavit ! maximum rlocal value for node j over all blades
1084+
real(ReKi) :: Re, fzero
1085+
real(ReKi) :: Rtip ! maximum rlocal value for node j over all blades
11021086

11031087
integer(IntKi) :: i ! Generic index
11041088
integer(IntKi) :: j ! Loops through nodes / elements
@@ -1178,12 +1162,6 @@ subroutine BEMT_CalcOutput( t, u, p, x, xd, z, OtherState, AFInfo, y, m, errStat
11781162

11791163
NodeTxt = '(node '//trim(num2lstr(i))//', blade '//trim(num2lstr(j))//')'
11801164

1181-
! local velocities and twist angle
1182-
Vx = u%Vx(i,j)
1183-
Vy = u%Vy(i,j)
1184-
1185-
1186-
11871165
! Set the active blade element for UnsteadyAero
11881166
m%UA%iBladeNode = i
11891167
m%UA%iBlade = j
@@ -1257,34 +1235,9 @@ subroutine BEMT_CalcOutput( t, u, p, x, xd, z, OtherState, AFInfo, y, m, errStat
12571235
else
12581236
! TODO: When we start using Re, should we use the uninduced Re since we used uninduced Re to solve for the inductions!? Probably this won't change, instead create a Re loop up above.
12591237
call ComputeSteadyAirfoilCoefs( y%AOA(i,j), y%Re(i,j), AFInfo(p%AFindx(i,j)), &
1260-
y%Cl(i,j), y%Cd(i,j), y%Cm(i,j), m%Cpmin(i,j), errStat2, errMsg2 )
1238+
y%Cl(i,j), y%Cd(i,j), y%Cm(i,j), errStat2, errMsg2 )
12611239
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName//trim(NodeTxt))
12621240
if (errStat >= AbortErrLev) return
1263-
1264-
1265-
1266-
1267-
! Calculate the cavitation number for the airfoil at the node in quesiton, and compare to the critical cavitation number based on the vapour pressure and submerged depth
1268-
if ( p%CavitCheck ) then
1269-
SigmaCavit= -1* m%Cpmin(i,j) ! Cavitation number on blade node j
1270-
1271-
if ( EqualRealNos( y%Vrel(i,j), 0.0_ReKi ) ) then !if Vrel = 0 in certain cases when Prandtls tip and hub loss factors are used, use the relative verlocity without induction
1272-
if ( EqualRealNos( Vx, 0.0_ReKi ) .and. EqualRealNos( Vy, 0.0_ReKi ) ) call SetErrStat( ErrID_Fatal, 'Velocity can not be zero for cavitation check, turn off Prandtls tip loss', ErrStat, ErrMsg, RoutineName )
1273-
SigmaCavitCrit= ( ( p%Patm + ( 9.81_ReKi * (p%FluidDepth - ( u%rlocal(i,j))* cos(u%psi(j) )) * p%airDens)) - p%Pvap ) / ( 0.5_ReKi * p%airDens * (sqrt((Vx**2 + Vy**2)))**2) ! Critical value of Sigma, cavitation if we go over this
1274-
1275-
else
1276-
SigmaCavitCrit= ( ( p%Patm + ( 9.81_ReKi * (p%FluidDepth - ( u%rlocal(i,j))* cos(u%psi(j) )) * p%airDens)) - p%Pvap ) / ( 0.5_ReKi * p%airDens * y%Vrel(i,j)**2) ! Critical value of Sigma, cavitation if we go over this
1277-
end if
1278-
1279-
1280-
if (SigmaCavitCrit < SigmaCavit) then
1281-
call WrScr( NewLine//'Cavitation occured at node # = '//trim(num2lstr(i)//'and blade # = '//trim(num2lstr(j))))
1282-
end if
1283-
1284-
m%SigmaCavit(i,j)= SigmaCavit
1285-
m%SigmaCavitCrit(i,j)=SigmaCavitCrit
1286-
1287-
end if
12881241
end if
12891242

12901243

@@ -1850,7 +1803,6 @@ subroutine BEMT_UnCoupledSolve( phi, numBlades, airDens, mu, AFInfo, rlocal, cho
18501803
integer :: i, TestRegionResult
18511804
logical :: IsValidSolution
18521805
real(ReKi) :: Re, Vrel
1853-
18541806

18551807
ErrStat = ErrID_None
18561808
ErrMsg = ""
@@ -1979,8 +1931,5 @@ end subroutine BEMT_UnCoupledSolve
19791931

19801932

19811933

1982-
end module BEMT
1983-
1984-
1985-
1986-
1934+
end module BEMT
1935+

0 commit comments

Comments
 (0)