Skip to content

Commit

Permalink
AD: Starting new input file format
Browse files Browse the repository at this point in the history
  • Loading branch information
ebranlard committed Nov 30, 2023
1 parent 201344e commit d6a10ea
Show file tree
Hide file tree
Showing 5 changed files with 166 additions and 27 deletions.
12 changes: 6 additions & 6 deletions modules/aerodyn/src/AeroDyn_Driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -52,24 +52,24 @@ program AeroDyn_Driver
! Init of time estimator
t_global=0.0_DbKi
t_final=dat%dvr%numSteps*dat%dvr%dt
if (dat%dvr%analysisType/=idAnalysisCombi) then
!if (dat%dvr%analysisType/=idAnalysisCombi) then
call SimStatus_FirstTime( TiLstPrn, PrevClockTime, SimStrtTime, UsrTime2, t_global, t_final )
endif
!endif

! One time loop
do nt = 1, dat%dvr%numSteps
call Dvr_TimeStep(nt, dat%dvr, dat%ADI, dat%FED, dat%errStat, dat%errMsg); call CheckError()
! Time update to screen
t_global=nt*dat%dvr%dt
if (dat%dvr%analysisType/=idAnalysisCombi) then
!if (dat%dvr%analysisType/=idAnalysisCombi) then
if (mod( nt + 1, 10 )==0) call SimStatus(TiLstPrn, PrevClockTime, t_global, t_final)
endif
!endif
end do !nt=1,numSteps

if (dat%dvr%analysisType/=idAnalysisCombi) then
!if (dat%dvr%analysisType/=idAnalysisCombi) then
! display runtime to screen
call RunTimes(StrtTime, UsrTime1, SimStrtTime, UsrTime2, t_global)
endif
!endif

call Dvr_EndCase(dat%dvr, dat%ADI, dat%initialized, dat%errStat, dat%errMsg); call CheckError()

Expand Down
113 changes: 103 additions & 10 deletions modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -659,6 +659,7 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
integer(IntKi) :: CurLine !< current entry in FileInfo_In%Lines array
real(ReKi) :: TmpRe5(5) !< temporary 8 number array for reading values in
character(1024) :: sDummy !< temporary string
logical :: frozenWakeProvided, AFAeroModProvided, isLegalComment !< Temporary for legacy purposes

character(*), parameter :: RoutineName = 'ParsePrimaryFileInfo'

Expand Down Expand Up @@ -703,12 +704,11 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
! DTAero - Time interval for aerodynamic calculations {or default} (s):
call ParseVarWDefault ( FileInfo_In, CurLine, "DTAero", InputFileData%DTAero, interval, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
! WakeMod - Type of wake/induction model (switch) {0=none, 1=BEMT, 2=DBEMT, 3=OLAF} [WakeMod cannot be 2 or 3 when linearizing]
call ParseVar( FileInfo_In, CurLine, "WakeMod", InputFileData%WakeMod, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
! AFAeroMod - Type of blade airfoil aerodynamics model (switch) {1=steady model, 2=Beddoes-Leishman unsteady model} [AFAeroMod must be 1 when linearizing]
! WakeMod - Type of wake/induction model (switch) {0=none, 1=BEMT, 2=TBD, 3=OLAF} [WakeMod cannot be 2 or 3 when linearizing]
call ParseVar( FileInfo_In, CurLine, "WakeMod", InputFileData%WakeMod, ErrStat2, ErrMsg2, UnEc ); if (Failed()) return
! AFAeroMod - Type of blade airfoil aerodynamics model (switch) {1=steady model, 2=Beddoes-Leishman unsteady model} [AFAeroMod must be 1 when linearizing]
call ParseVar( FileInfo_In, CurLine, "AFAeroMod", InputFileData%AFAeroMod, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
AFAeroModProvided = legacyInputPresent('AFAeroMod', CurLine, ErrStat2, ErrMsg2, 'UAMod=0 (AFAeroMod=1), UAMod>1 (AFAeroMod=2)')
! TwrPotent - Type of tower influence on wind based on potential flow around the tower (switch) {0=none, 1=baseline potential flow, 2=potential flow with Bak correction}
call ParseVar( FileInfo_In, CurLine, "TwrPotent", InputFileData%TwrPotent, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
Expand All @@ -718,9 +718,9 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
! TwrAero - Calculate tower aerodynamic loads? (flag)
call ParseVar( FileInfo_In, CurLine, "TwrAero", InputFileData%TwrAero, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
! FrozenWake - Assume frozen wake during linearization? (flag) [used only when WakeMod=1 and when linearizing]
! FrozenWake - Assume frozen wake during linearization? (flag) [used only when WakeMod=1 and when linearizing]
call ParseVar( FileInfo_In, CurLine, "FrozenWake", InputFileData%FrozenWake, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
frozenWakeProvided = legacyInputPresent('FrozenWake', Curline, ErrStat2, ErrMsg2, 'DBEMTMod=-1 (FrozenWake=True), DBEMTMod>-1 (FrozenWake=False)')
! CavitCheck - Perform cavitation check? (flag) [AFAeroMod must be 1 when CavitCheck=true]
call ParseVar( FileInfo_In, CurLine, "CavitCheck", InputFileData%CavitCheck, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
Expand Down Expand Up @@ -788,11 +788,21 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
! MaxIter - Maximum number of iteration steps (-) [unused when WakeMod=0]
call ParseVar( FileInfo_In, CurLine, "MaxIter", InputFileData%MaxIter, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
! --- Shear
call ParseCom (FileInfo_in, CurLine, sDummy, errStat2, errMsg2, UnEc, isLegalComment);
if (newInputAbsent('Comment line `--- Shear`', CurLine, errStat2, errMsg2)) then
! pass
else
call ParseVar( FileInfo_In, CurLine, "SectAvg" , InputFileData%SectAvg, ErrStat2, ErrMsg2, UnEc ); if (Failed()) return
call ParseVar( FileInfo_In, CurLine, "SectAvgWeighting", InputFileData%SA_Weighting, ErrStat2, ErrMsg2, UnEc ); if (Failed()) return
call ParseVar( FileInfo_In, CurLine, "SectAvgNPoints" , InputFileData%SA_nPerSec, ErrStat2, ErrMsg2, UnEc ); if (Failed()) return
endif


!====== Dynamic Blade-Element/Momentum Theory Options ============================================== [used only when WakeMod=2]
if ( InputFileData%Echo ) WRITE(UnEc, '(A)') FileInfo_In%Lines(CurLine) ! Write section break to echo
CurLine = CurLine + 1
! DBEMT_Mod - Type of dynamic BEMT (DBEMT) model {1=constant tau1, 2=time-dependent tau1} (-) [used only when WakeMod=2]
call ParseCom (FileInfo_in, CurLine, sDummy, errStat2, errMsg2, UnEc, isLegalComment); if (Failed()) return

! DBEMT_Mod - Type of dynamic BEMT (DBEMT) model {1=constant tau1, 2=time-dependent tau1} (-) [used only when WakeMod=2]
call ParseVar( FileInfo_In, CurLine, "DBEMT_Mod", InputFileData%DBEMT_Mod, ErrStat2, ErrMsg2, UnEc )
if (Failed()) return
! tau1_const - Time constant for DBEMT (s) [used only when WakeMod=2 and DBEMT_Mod=1]
Expand Down Expand Up @@ -1021,6 +1031,45 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
if (InputFileData%BldNd_BladesOut <= 0) InputFileData%BldNd_NumOuts = 0


!====== Legacy logic to match old and new input files ================================================
! NOTE: remove me in future release
if (frozenWakeProvided) then
if (InputFileData%FrozenWake) then
call WrScr(' FrozenWake=True -> Setting DBEMT_Mod=-1')
! InputFileData%DBEMT_Mod =-1
else
call WrScr(' FrozenWake=False -> Not changing DBEMT_Mod')
endif
endif
if (AFAeroModProvided) then
if (InputFileData%AFAeroMod==1) then
call WrScr(' AFAeroMod=1 -> Setting UAMod=0')
! InputFileData%UAMod=0
else if (InputFileData%AFAeroMod==1) then
call WrScr(' AFAeroMod=2 -> Not changing DBEMT_Mod')
else
call LegacyAbort('AFAeroMod should be 1 or 2'); return
endif
endif

!====== Summary of new AeroDyn options ===============================================================
! NOTE: remove me in future release
call WrScr('-------------- New AeroDyn inputs (with new meaning):')
write (*,'(A20,I0)') 'WakeMod: ' , InputFileData%WakeMod
write (*,'(A20,L0)') 'SectAvg: ' , InputFileData%SectAvg
write (*,'(A20,I0)') 'SectAvgWeighting: ', InputFileData%SA_Weighting
write (*,'(A20,I0)') 'SectAvgNPoints: ', InputFileData%SA_nPerSec
write (*,'(A20,I0)') 'DBEMT_Mod:' , InputFileData%DBEMT_Mod
write (*,'(A20,I0)') 'SkewMod: ' , InputFileData%SkewMod
write (*,'(A20,L0)') 'SkewMomCorr:' , InputFileData%SkewMomCorr
write (*,'(A20,I0)') 'SkewRedistrMod:' , InputFileData%SkewRedistrMod
write (*,'(A20,L0)') 'AoA34: ' , InputFileData%AoA34
write (*,'(A20,I0)') 'UAMod: ' , InputFileData%UAMod
call WrScr('-------------- Old AeroDyn inputs:')
write (*,'(A20,I0)') 'AFAeroMod:', InputFileData%AFAeroMod
write (*,'(A20,L0)') 'FrozenWake:', InputFileData%FrozenWake
call WrScr('------------------------------------------------------')

!====== Advanced Options =============================================================================
if ((CurLine) >= size(FileInfo_In%Lines)) RETURN

Expand All @@ -1047,6 +1096,8 @@ SUBROUTINE ParsePrimaryFileInfo( PriPath, InitInp, InputFile, RootName, NumBlade
endif
enddo



RETURN
CONTAINS
!-------------------------------------------------------------------------------------------------
Expand Down Expand Up @@ -1074,6 +1125,48 @@ subroutine LegacyWarning(Message)
call WrScr('!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!')
end subroutine LegacyWarning
!-------------------------------------------------------------------------------------------------
subroutine LegacyAbort(Message)
character(len=*), intent(in) :: Message
call SetErrStat( ErrID_Fatal, Message, ErrStat, ErrMsg, 'ParsePrimaryFileInfo' )
end subroutine LegacyAbort
!-------------------------------------------------------------------------------------------------
logical function legacyInputPresent(varName, iLine, errStat, errMsg, varNameSubs)
character(len=*), intent(in ) :: varName !< Variable being read
integer(IntKi), intent(in ) :: iLine !< Line number
integer(IntKi), intent(inout) :: errStat !< Error status
character(ErrMsgLen), intent(inout) :: errMsg !< Error message
character(len=*), optional, intent(in ) :: varNameSubs !< Substituted variable
legacyInputPresent = errStat == ErrID_None
if (legacyInputPresent) then
if (present(varNameSubs)) then
call LegacyWarning('Input '//trim(varName)//' has now been removed.'//NewLine//'Replaced by: '//trim(varNameSubs)//'.')
else
call LegacyWarning('Input '//trim(varName)//' has now been removed.')
endif
else
! We are actually happy, this input should indeed not be present.
endif
! We erase the error no matter what
errStat = ErrID_None
errMsg = ''
end function legacyInputPresent
!-------------------------------------------------------------------------------------------------
logical function newInputAbsent(varName, iLine, errStat, errMsg, varNameSubs)
character(len=*), intent(in ) :: varName !< Variable being read
integer(IntKi), intent(in ) :: iLine !< Line number
integer(IntKi), intent(inout) :: errStat !< Error status
character(ErrMsgLen), intent(inout) :: errMsg !< Error message
character(len=*), optional, intent(in ) :: varNameSubs !< Substituted variable
newInputAbsent = errStat == ErrID_Fatal
if (newInputAbsent) then
call LegacyWarning('Input '//trim(varName)//' should be present on line '//trim(num2lstr(iLine))//'.')
else
! We are happy
endif
! We erase the error
errStat = ErrID_None
errMsg = ''
end function newInputAbsent
END SUBROUTINE ParsePrimaryFileInfo
!----------------------------------------------------------------------------------------------------------------------------------
SUBROUTINE ReadBladeInputs ( ADBlFile, BladeKInputFileData, AeroProjMod, UnEc, ErrStat, ErrMsg )
Expand Down
15 changes: 10 additions & 5 deletions modules/aerodyn/src/AeroDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -166,6 +166,7 @@ typedef ^ RotInputFile TFinInputFileType TFin - - - "Input file
typedef ^ AD_InputFile Logical Echo - - - "Echo input file to echo file" -
typedef ^ AD_InputFile DbKi DTAero - - - "Time interval for aerodynamic calculations {or \"default\"}" s
typedef ^ AD_InputFile IntKi WakeMod - - - "Type of wake/induction model {0=none, 1=BEMT, 2=DBEMT, 3=FVW}" -
typedef ^ AD_InputFile IntKi BEMMod - - - "Type of BEM model {1=legacy NoSweepPitchTwist, 2=polar grid}" -
typedef ^ AD_InputFile IntKi AFAeroMod - - - "Type of blade airfoil aerodynamics model {1=steady model, 2=Beddoes-Leishman unsteady model}" -
typedef ^ AD_InputFile IntKi TwrPotent - - - "Type of tower influence on wind based on potential flow around the tower {0=none, 1=baseline potential flow, 2=potential flow with Bak correction}" -
typedef ^ AD_InputFile IntKi TwrShadow - - - "Type of tower influence on wind based on downstream tower shadow {0=none, 1=Powles model, 2=Eames model}" -
Expand All @@ -181,7 +182,9 @@ 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 {0=orthogonal, 1=uncoupled, 2=Pitt/Peters, 3=coupled} [unused when WakeMod=0]" -
typedef ^ AD_InputFile IntKi SkewMod - - - "Select skew model {0=No skew model at all, -1=Throw away non-normal component for linearization, 1=Glauert skew model}" -
typedef ^ AD_InputFile Logical SkewMomCorr - - - "Turn the skew momentum correction on or off [used only when SkewMod=1]" -
typedef ^ AD_InputFile IntKi SkewRedistrMod - - - "Type of skewed-wake correction model (switch) {0=no redistribution, 1=Glauert/Pitt/Peters, 2=Vortex Cylinder} [unsed only when SkewMod=1]" -
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 All @@ -190,11 +193,13 @@ typedef ^ AD_InputFile LOGICAL AIDrag - - - "Include the drag term in the axial-
typedef ^ AD_InputFile LOGICAL TIDrag - - - "Include the drag term in the tangential-induction calculation? [unused when WakeMod=0 or TanInd=FALSE]" flag
typedef ^ AD_InputFile ReKi IndToler - - - "Convergence tolerance for BEM induction factors [unused when WakeMod=0]" -
typedef ^ AD_InputFile ReKi MaxIter - - - "Maximum number of iteration steps [unused when WakeMod=0]" -
typedef ^ AD_InputFile Logical SectAvg - - False "Use Sector average for BEM inflow velocity calculation" -
typedef ^ AD_InputFile Logical SectAvg - - False "Use Sector average for BEM inflow velocity calculation (flag)" -
typedef ^ ^ IntKi SA_Weighting - - 1 "Sector Average - Weighting function for sector average {1=Uniform, 2=Impulse, } within a 360/nB sector centered on the blade (switch) [used only when SectAvg=True]" -
typedef ^ ^ ReKi SA_PsiBwd - -60 - "Sector Average - Backard Azimuth (<0)" deg
typedef ^ ^ ReKi SA_PsiFwd - 60 - "Sector Average - Forward Azimuth (>0)" deg
typedef ^ ^ IntKi SA_nPerSec - 11 - "Sector Average - Number of points per sectors (>1)" -
typedef ^ ^ IntKi UAMod - - - "Unsteady Aero Model Switch (switch) {1=Baseline model (Original), 2=Gonzalez's variant (changes in Cn,Cc,Cm), 3=Minnema/Pierce variant (changes in Cc and Cm)} [used only when AFAeroMod=2]" -
typedef ^ ^ IntKi SA_nPerSec - 11 - "Sector average - Number of points per sectors (-) [used only when SectAvg=True]" -
typedef ^ ^ IntKi AoA34 - - - "Sample the angle of attack (AoA) at the 3/4 chord or the AC point {default=True} [always used]" -
typedef ^ ^ IntKi UAMod - - - "Unsteady Aero Model Switch (switch) {0=Quasi-steady (no UA), 2=Gonzalez's variant (changes in Cn,Cc,Cm), 3=Minnema/Pierce variant (changes in Cc and Cm)}" -
typedef ^ AD_InputFile LOGICAL FLookup - - - "Flag to indicate whether a lookup for f' will be calculated (TRUE) or whether best-fit exponential equations will be used (FALSE); if FALSE S1-S4 must be provided in airfoil input files [used only when AFAeroMod=2]" flag
typedef ^ AD_InputFile ReKi InCol_Alfa - - - "The column in the airfoil tables that contains the angle of attack" -
typedef ^ AD_InputFile ReKi InCol_Cl - - - "The column in the airfoil tables that contains the lift coefficient" -
Expand All @@ -215,7 +220,7 @@ typedef ^ AD_InputFile IntKi TwOutNd {9} - - "Tower nodes whose values will be o
typedef ^ AD_InputFile IntKi NumOuts - - - "Number of parameters in the output list (number of outputs requested)" -
typedef ^ AD_InputFile CHARACTER(ChanLen) OutList {:} - - "List of user-requested output channels" -
typedef ^ AD_InputFile ReKi tau1_const - - - "time constant for DBEMT [used only when WakeMod=2 and DBEMT_Mod/=2]" s
typedef ^ AD_InputFile IntKi DBEMT_Mod - - - "Type of dynamic BEMT (DBEMT) model {1=constant tau1, 2=time-dependent tau1}" -
typedef ^ AD_InputFile IntKi DBEMT_Mod - - - "Type of dynamic BEMT (DBEMT) model {0=No Dynamic Wake, -1=Frozen Wake for linearization, 1=constant tau1, 2=time-dependent tau1, 3=constant tau1 with continuous formulation} (-) [used only when WakeMod=1]" -
typedef ^ AD_InputFile IntKi BldNd_NumOuts - - - "Number of requested output channels per blade node (AD_AllBldNdOuts)" -
typedef ^ AD_InputFile CHARACTER(ChanLen) BldNd_OutList {:} - - "List of user-requested output channels (AD_AllBldNdOuts)" -
#typedef ^ AD_InputFile IntKi BldNd_BlOutNd {:} - - "The blade nodes to actually output (AD_AllBldNdOuts)" -
Expand Down
Loading

0 comments on commit d6a10ea

Please sign in to comment.