Skip to content

Commit

Permalink
AD: adding SkewMod=0, for flow orthogonal to rotor
Browse files Browse the repository at this point in the history
# Conflicts:
#	modules/aerodyn/src/AeroDyn.f90
#	modules/aerodyn/src/AeroDyn_IO.f90
#	modules/aerodyn/src/AeroDyn_Registry.txt
#	modules/aerodyn/src/AeroDyn_Types.f90
  • Loading branch information
ebranlard authored and rafmudaf committed May 9, 2022
1 parent 8130a1b commit 189698b
Show file tree
Hide file tree
Showing 5 changed files with 32 additions and 7 deletions.
22 changes: 18 additions & 4 deletions modules/aerodyn/src/AeroDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -325,6 +325,7 @@ subroutine AD_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitOut


! set the rest of the parameters
p%SkewMod = InputFileData%SkewMod
do iR = 1, nRotors
p%rotors(iR)%AeroProjMod = InitInp%rotors(iR)%AeroProjMod
call SetParameters( InitInp, InputFileData, InputFileData%rotors(iR), p%rotors(iR), p, ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -1660,7 +1661,7 @@ subroutine SetInputs(p, p_AD, u, m, indx, errStat, errMsg)
ErrMsg = ""

! Disturbed inflow on blade (if tower shadow present)
call SetDisturbedInflow(p, u, m, errStat, errMsg)
call SetDisturbedInflow(p, p_AD, u, m, errStat, errMsg)

if (p_AD%WakeMod /= WakeMod_FVW) then
! This needs to extract the inputs from the AD data types (mesh) and massage them for the BEMT module
Expand All @@ -1671,13 +1672,16 @@ end subroutine SetInputs

!----------------------------------------------------------------------------------------------------------------------------------
!> Disturbed inflow on the blade if tower shadow or tower influence are enabled
subroutine SetDisturbedInflow(p, u, m, errStat, errMsg)
subroutine SetDisturbedInflow(p, p_AD, u, m, errStat, errMsg)
type(RotParameterType), intent(in ) :: p !< AD parameters
type(AD_ParameterType), intent(in ) :: p_AD !< AD parameters
type(RotInputType), intent(in ) :: u !< AD Inputs at Time
type(RotMiscVarType), intent(inout) :: m !< Misc/optimization variables
integer(IntKi), intent( out) :: errStat !< Error status of the operation
character(*), intent( out) :: errMsg !< Error message if ErrStat /= ErrID_None
! local variables
real(R8Ki) :: x_hat_disk(3)
integer(intKi) :: j,k
integer(intKi) :: errStat2
character(ErrMsgLen) :: errMsg2
character(*), parameter :: RoutineName = 'SetDisturbedInflow'
Expand All @@ -1690,6 +1694,16 @@ subroutine SetDisturbedInflow(p, u, m, errStat, errMsg)
m%DisturbedInflow = u%InflowOnBlade
end if

if (p_AD%SkewMod == SkewMod_Orthogonal) then
x_hat_disk = u%HubMotion%Orientation(1,:,1)

do k=1,p%NumBlades
do j=1,p%NumBlNds
m%DisturbedInflow(:,j,k) = dot_product( m%DisturbedInflow(:,j,k), x_hat_disk ) * x_hat_disk
enddo
enddo
endif

end subroutine SetDisturbedInflow


Expand Down Expand Up @@ -2020,7 +2034,7 @@ subroutine SetInputsForFVW(p, u, m, errStat, errMsg)
endif
do iR =1, size(p%rotors)
! Disturbed inflow for UA on Lifting line Mesh Points
call SetDisturbedInflow(p%rotors(iR), u(tIndx)%rotors(iR), m%rotors(iR), errStat, errMsg)
call SetDisturbedInflow(p%rotors(iR), p, u(tIndx)%rotors(iR), m%rotors(iR), errStat, errMsg)
do k=1,p%rotors(iR)%NumBlades
iW=p%FVW%Bld2Wings(iR,k)
m%FVW_u(tIndx)%W(iW)%Vwnd_LL(1:3,:) = m%rotors(iR)%DisturbedInflow(1:3,:,k)
Expand Down Expand Up @@ -2340,7 +2354,7 @@ SUBROUTINE ValidateInputData( InitInp, InputFileData, NumBl, ErrStat, ErrMsg )
if ( InputFileData%IndToler < 0.0 .or. EqualRealNos(InputFileData%IndToler, 0.0_ReKi) ) &
call SetErrStat( ErrID_Fatal, 'IndToler must be greater than 0.', ErrStat, ErrMsg, RoutineName )

if ( InputFileData%SkewMod /= SkewMod_Uncoupled .and. InputFileData%SkewMod /= SkewMod_PittPeters) & ! .and. InputFileData%SkewMod /= SkewMod_Coupled )
if ( InputFileData%SkewMod /= SkewMod_Orthogonal .and. InputFileData%SkewMod /= SkewMod_Uncoupled .and. InputFileData%SkewMod /= SkewMod_PittPeters) & ! .and. InputFileData%SkewMod /= SkewMod_Coupled )
call SetErrStat( ErrID_Fatal, 'SkewMod must be 1, or 2. Option 3 will be implemented in a future version.', ErrStat, ErrMsg, RoutineName )

end if !BEMT/DBEMT checks
Expand Down
4 changes: 3 additions & 1 deletion modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ MODULE AeroDyn_IO

use NWTC_Library
use AeroDyn_Types
use BEMTUncoupled, only : SkewMod_Uncoupled, SkewMod_PittPeters, VelocityIsZero
use BEMTUncoupled, only : SkewMod_Orthogonal, SkewMod_Uncoupled, SkewMod_PittPeters, VelocityIsZero
use FVW_Subs, only : FVW_AeroOuts

USE AeroDyn_AllBldNdOuts_IO
Expand Down Expand Up @@ -2700,6 +2700,8 @@ SUBROUTINE AD_PrintSum( InputFileData, p, p_AD, u, y, ErrStat, ErrMsg )

! SkewMod
select case (InputFileData%SkewMod)
case (SkewMod_Orthogonal)
Msg = 'orthogonal'
case (SkewMod_Uncoupled)
Msg = 'uncoupled'
case (SkewMod_PittPeters)
Expand Down
3 changes: 2 additions & 1 deletion modules/aerodyn/src/AeroDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ typedef ^ AD_InputFile ReKi KinVisc - - - "Kinematic air viscosity" m^2/s
typedef ^ AD_InputFile ReKi Patm - - - "Atmospheric pressure" Pa
typedef ^ AD_InputFile ReKi Pvap - - - "Vapour pressure" Pa
typedef ^ AD_InputFile ReKi SpdSound - - - "Speed of sound" m/s
typedef ^ AD_InputFile IntKi SkewMod - - - "Type of skewed-wake correction model {1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0]" -
typedef ^ AD_InputFile IntKi SkewMod - - - "Type of skewed-wake correction model {0=orthogonal, 1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0]" -
typedef ^ AD_InputFile ReKi SkewModFactor - - - "Constant used in Pitt/Peters skewed wake model (default is 15*pi/32)" -
typedef ^ AD_InputFile LOGICAL TipLoss - - - "Use the Prandtl tip-loss model? [unused when WakeMod=0]" flag
typedef ^ AD_InputFile LOGICAL HubLoss - - - "Use the Prandtl hub-loss model? [unused when WakeMod=0]" flag
Expand Down Expand Up @@ -284,6 +284,7 @@ typedef ^ ParameterType RotParameterType rotors {:} - - "Parameter types for
typedef ^ ParameterType DbKi DT - - - "Time step for continuous state integration & discrete state update" seconds
typedef ^ ParameterType CHARACTER(1024) RootName - - - "RootName for writing output files" -
typedef ^ ParameterType AFI_ParameterType AFI {:} - - "AirfoilInfo parameters"
typedef ^ ParameterType IntKi SkewMod - - - "Type of skewed-wake correction model {0=orthogonal, 1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0]" -
typedef ^ ParameterType IntKi WakeMod - - - "Type of wake/induction model {0=none, 1=BEMT, 2=DBEMT, 3=FVW}" -
typedef ^ ParameterType FVW_ParameterType FVW - - - "Parameters for FVW module"
typedef ^ ParameterType LOGICAL UA_Flag - - - "logical flag indicating whether to use UnsteadyAero" -
Expand Down
9 changes: 8 additions & 1 deletion modules/aerodyn/src/AeroDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ MODULE AeroDyn_Types
REAL(ReKi) :: Patm !< Atmospheric pressure [Pa]
REAL(ReKi) :: Pvap !< Vapour pressure [Pa]
REAL(ReKi) :: SpdSound !< Speed of sound [m/s]
INTEGER(IntKi) :: SkewMod !< Type of skewed-wake correction model {1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0] [-]
INTEGER(IntKi) :: SkewMod !< Type of skewed-wake correction model {0=orthogonal, 1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0] [-]
REAL(ReKi) :: SkewModFactor !< Constant used in Pitt/Peters skewed wake model (default is 15*pi/32) [-]
LOGICAL :: TipLoss !< Use the Prandtl tip-loss model? [unused when WakeMod=0] [flag]
LOGICAL :: HubLoss !< Use the Prandtl hub-loss model? [unused when WakeMod=0] [flag]
Expand Down Expand Up @@ -328,6 +328,7 @@ MODULE AeroDyn_Types
REAL(DbKi) :: DT !< Time step for continuous state integration & discrete state update [seconds]
CHARACTER(1024) :: RootName !< RootName for writing output files [-]
TYPE(AFI_ParameterType) , DIMENSION(:), ALLOCATABLE :: AFI !< AirfoilInfo parameters [-]
INTEGER(IntKi) :: SkewMod !< Type of skewed-wake correction model {0=orthogonal, 1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0] [-]
INTEGER(IntKi) :: WakeMod !< Type of wake/induction model {0=none, 1=BEMT, 2=DBEMT, 3=FVW} [-]
TYPE(FVW_ParameterType) :: FVW !< Parameters for FVW module [-]
LOGICAL :: UA_Flag !< logical flag indicating whether to use UnsteadyAero [-]
Expand Down Expand Up @@ -11174,6 +11175,7 @@ SUBROUTINE AD_CopyParam( SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg )
IF (ErrStat>=AbortErrLev) RETURN
ENDDO
ENDIF
DstParamData%SkewMod = SrcParamData%SkewMod
DstParamData%WakeMod = SrcParamData%WakeMod
CALL FVW_CopyParam( SrcParamData%FVW, DstParamData%FVW, CtrlCode, ErrStat2, ErrMsg2 )
CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg,RoutineName)
Expand Down Expand Up @@ -11289,6 +11291,7 @@ SUBROUTINE AD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si
END IF
END DO
END IF
Int_BufSz = Int_BufSz + 1 ! SkewMod
Int_BufSz = Int_BufSz + 1 ! WakeMod
Int_BufSz = Int_BufSz + 3 ! FVW: size of buffers for each call to pack subtype
CALL FVW_PackParam( Re_Buf, Db_Buf, Int_Buf, InData%FVW, ErrStat2, ErrMsg2, .TRUE. ) ! FVW
Expand Down Expand Up @@ -11423,6 +11426,8 @@ SUBROUTINE AD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si
ENDIF
END DO
END IF
IntKiBuf(Int_Xferred) = InData%SkewMod
Int_Xferred = Int_Xferred + 1
IntKiBuf(Int_Xferred) = InData%WakeMod
Int_Xferred = Int_Xferred + 1
CALL FVW_PackParam( Re_Buf, Db_Buf, Int_Buf, InData%FVW, ErrStat2, ErrMsg2, OnlySize ) ! FVW
Expand Down Expand Up @@ -11602,6 +11607,8 @@ SUBROUTINE AD_UnPackParam( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg
IF(ALLOCATED(Int_Buf)) DEALLOCATE(Int_Buf)
END DO
END IF
OutData%SkewMod = IntKiBuf(Int_Xferred)
Int_Xferred = Int_Xferred + 1
OutData%WakeMod = IntKiBuf(Int_Xferred)
Int_Xferred = Int_Xferred + 1
Buf_size=IntKiBuf( Int_Xferred )
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/BEMTUncoupled.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ module BEMTUnCoupled

implicit none

integer(IntKi), public, parameter :: SkewMod_Orthogonal = 0 ! Inflow orthogonal to rotor [-]
integer(IntKi), public, parameter :: SkewMod_Uncoupled = 1 ! Uncoupled (no correction) [-]
integer(IntKi), public, parameter :: SkewMod_PittPeters = 2 ! Pitt/Peters [-]
integer(IntKi), public, parameter :: SkewMod_Coupled = 3 ! Coupled [-]
Expand Down

0 comments on commit 189698b

Please sign in to comment.