Skip to content

Commit

Permalink
UA: using p%UA_OUTS instead of precompiler flag
Browse files Browse the repository at this point in the history
  • Loading branch information
ebranlard committed Oct 4, 2023
1 parent d263e47 commit cf21289
Show file tree
Hide file tree
Showing 5 changed files with 103 additions and 68 deletions.
1 change: 1 addition & 0 deletions modules/aerodyn/src/UA_Dvr_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -437,6 +437,7 @@ subroutine driverInputsToUAInitData(dvrInitInp, InitInData, AFI_Params, AFIndx,
character(*), parameter :: RoutineName = 'driverInputsToUAInitData'
errStat = ErrID_None
errMsg = ''
InitInData%UA_OUTS = 2 ! 0=None, 1=Write Outputs, 2=Separate File

! -- UA Init Input Data
InitInData%nNodesPerBlade = 1
Expand Down
138 changes: 76 additions & 62 deletions modules/aerodyn/src/UnsteadyAero.f90
Original file line number Diff line number Diff line change
Expand Up @@ -744,6 +744,10 @@ subroutine UA_SetParameters( dt, InitInp, p, AFInfo, AFIndx, ErrStat, ErrMsg )
p%a_s = InitInp%a_s ! this can't be 0
p%Flookup = InitInp%Flookup
p%ShedEffect = InitInp%ShedEffect
p%UA_OUTS = InitInp%UA_OUTS
#ifdef UA_OUTS
p%UA_OUTS = 2 ! Compiler Flag Override, 2=Write a separate file
#endif

if (p%UAMod==UA_HGM .or. p%UAMod==UA_HGMV) then
p%lin_nx = p%numBlades*p%nNodesPerBlade*4 ! 4 continuous states per node per blade (5th state isn't currently linearizable)
Expand Down Expand Up @@ -901,13 +905,12 @@ subroutine UA_InitStates_Misc( p, x, xd, OtherState, m, ErrStat, ErrMsg )
call AllocAry(OtherState%sigma1m ,p%nNodesPerBlade,p%numBlades,'OtherState%sigma1m',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(OtherState%sigma3 ,p%nNodesPerBlade,p%numBlades,'OtherState%sigma3',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)


# ifdef UA_OUTS
if(p%UA_OUTS>0) then
call AllocAry(m%TESF ,p%nNodesPerBlade,p%numBlades,'m%TESF',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(m%LESF ,p%nNodesPerBlade,p%numBlades,'m%LESF',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(m%VRTX ,p%nNodesPerBlade,p%numBlades,'m%VRTX',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(m%T_Sh ,p%nNodesPerBlade,p%numBlades,'m%T_Sh',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
# endif
endif
end if

call AllocAry(m%weight ,p%nNodesPerBlade,p%numBlades,'m%weight',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
Expand Down Expand Up @@ -996,12 +999,12 @@ subroutine UA_ReInit( p, x, xd, OtherState, m, ErrStat, ErrMsg )
OtherState%sigma1m = 1.0_ReKi
OtherState%sigma3 = 1.0_ReKi

# ifdef UA_OUTS
if (p%UA_OUTS>0) then
m%TESF = .FALSE.
m%LESF = .FALSE.
m%VRTX = .FALSE.
m%T_sh = 0.0_ReKi
# endif
endif

xd%Cn_prime_minus1 = 0.0_ReKi
xd%alpha_minus1 = 0.0_ReKi
Expand Down Expand Up @@ -1075,12 +1078,6 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
integer(IntKi) :: errStat2 ! temporary Error status of the operation
character(*), parameter :: RoutineName = 'UA_Init'

#ifdef UA_OUTS
CHARACTER(6) :: TmpChar ! Temporary char array to hold the node digits (3 places only!!!!)
integer(IntKi) :: i,j, iNode, iOffset
character(64) :: chanPrefix
#endif

! Initialize variables for this routine
ErrStat = ErrID_None
ErrMsg = ""
Expand All @@ -1090,27 +1087,50 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
call NWTC_Init( EchoLibVer=.FALSE. )

if (InitInp%WrSum) then
call UA_WriteAFIParamsToFile(InitInp, AFInfo, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
call UA_WriteAFIParamsToFile(InitInp, AFInfo, ErrStat2, ErrMsg2); if(Failed()) return
end if

call UA_ValidateInput(InitInp, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
call UA_ValidateInput(InitInp, ErrStat2, ErrMsg2); if(Failed()) return

! Allocate and set parameter data structure using initialization data
call UA_SetParameters( interval, InitInp, p, AFInfo, AFIndx, ErrStat2, ErrMsg2 )
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
call UA_SetParameters( interval, InitInp, p, AFInfo, AFIndx, ErrStat2, ErrMsg2 ); if(Failed()) return

! initialize the discrete states, other states, and misc variables
call UA_InitStates_Misc( p, x, xd, OtherState, m, ErrStat2, ErrMsg2 ) ! initialize the continuous states
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
! initialize the states, and misc variables
call UA_InitStates_Misc( p, x, xd, OtherState, m, ErrStat2, ErrMsg2 ); if(Failed()) return

! --- Write Outputs
call UA_Init_Outputs(InitInp, p, y, InitOut, errStat2, errMsg2); if(Failed()) return

#ifdef UA_OUTS
contains
logical function Failed()
call SetErrStat( errStat2, errMsg2, errStat, errMsg, 'UA_Init' )
Failed = errStat >= AbortErrLev
end function Failed
end subroutine UA_Init

!==============================================================================
subroutine UA_Init_Outputs(InitInp, p, y, InitOut, errStat, errMsg)
type(UA_InitInputType), intent(in ) :: InitInp ! input data for initialization routine ; we're moving allocated data from InitInp to p so must also be intent(out)
type(UA_ParameterType), intent(inout) :: p ! Parameters
type(UA_OutputType), intent(inout) :: y ! Initial system outputs (outputs are not calculated;
!type(UA_MiscVarType), intent( out) :: m ! Initial misc/optimization variables
type(UA_InitOutputType), intent( out) :: InitOut ! Output for initialization routine
integer(IntKi), intent( out) :: ErrStat ! Error status of the operation
character(*), intent( out) :: ErrMsg ! Error message if ErrStat /= ErrID_None
character(6) :: TmpChar ! Temporary char array to hold the node digits (3 places only!!!!)
integer(IntKi) :: i,j, iNode, iOffset
character(64) :: chanPrefix
character(ErrMsgLen) :: errMsg2 ! temporary Error message if ErrStat /= ErrID_None
integer(IntKi) :: errStat2 ! temporary Error status of the operation
character(*), parameter :: RoutineName = 'UA_Init'
errStat = errID_None
errMsg = ""

if (p%UA_OUTS==0) then
p%NumOuts = 0
p%unOutFile = -1
return
endif

! Allocate and set the InitOut data
if (p%UAMod == UA_HGM .or. p%UAMod == UA_OYE) then
Expand Down Expand Up @@ -1139,8 +1159,12 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
iOffset = (i-1)*p%NumOuts + (j-1)*p%nNodesPerBlade*p%NumOuts

!chanPrefix = "B"//trim(num2lstr(j))//"N"//trim(num2lstr(i))
write (TmpChar,'(I3.3)') i ! 3 digit number
chanPrefix = 'AB' // TRIM(Num2LStr(j)) // 'N' // TRIM(TmpChar)
if ((p%numBlades==1) .and. (p%nNodesPerBlade==1) .and. p%UA_OUTS==1) then
chanPrefix='' ! UA_Driver
else
write (TmpChar,'(I3.3)') i ! 3 digit number
chanPrefix = 'AB' // TRIM(Num2LStr(j)) // 'N' // TRIM(TmpChar)
endif

InitOut%WriteOutputHdr(iOffset+ 1) = trim(chanPrefix)//'Alpha'
InitOut%WriteOutputHdr(iOffset+ 2) = trim(chanPrefix)//'Vrel'
Expand Down Expand Up @@ -1327,7 +1351,9 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
p%OutFmt = 'ES19.5e3'
p%Delim =''

if (p%NumOuts > 0) then
! --- Write to File
if ((p%NumOuts > 0) .and. p%UA_OUTS==2) then
call WrScr(' UA: Writing separate output file: '//trim((InitInp%OutRootName)//'.UA.out'))
CALL GetNewUnit( p%unOutFile, ErrStat2, ErrMsg2 )
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
Expand All @@ -1351,21 +1377,12 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
WRITE (p%unOutFile,'(:,A,'//trim( p%OutSFmt )//')', ADVANCE='no' ) p%Delim, trim(InitOut%WriteOutputUnt(i))
end do
WRITE (p%unOutFile,'()', IOSTAT=ErrStat2) ! write the line return
end if

elseif ((p%NumOuts > 0) .and. p%UA_OUTS==2) then

#else
p%NumOuts = 0
p%unOutFile = -1
!.....................................
! add the following two lines only to avoid compiler warnings about uninitialized variables when not building the UA driver:
y%cm = 0.0_ReKi
InitOut%Version = ProgDesc( 'Unsteady Aero', '', '' )
!.....................................

#endif

end subroutine UA_Init
call WrScr(' UA: saving write outputs')

end if
end subroutine UA_Init_Outputs
!==============================================================================
subroutine UA_ValidateInput(InitInp, ErrStat, ErrMsg)
type(UA_InitInputType), intent(in ) :: InitInp ! Input data for initialization routine
Expand Down Expand Up @@ -2171,12 +2188,12 @@ subroutine UA_UpdateDiscOtherState( i, j, u, p, xd, OtherState, AFInfo, m, ErrSt
end if
end if

#ifdef UA_OUTS
if (p%UA_OUTS>0) then
m%TESF(i,j) = TESF
m%LESF(i,j) = LESF
m%VRTX(i,j) = VRTX
m%T_sh(i,j) = T_sh
#endif
endif


end subroutine UA_UpdateDiscOtherState
Expand Down Expand Up @@ -3065,19 +3082,14 @@ subroutine UA_CalcOutput( i, j, t, u_in, p, x, xd, OtherState, AFInfo, y, misc,
real(ReKi) :: alphaE_L, alphaE_D ! effective angle of attack for lift and drag
real(ReKi) :: alphaLag_D ! lagged angle of attack for drag calculation
real(ReKi) :: adotnorm
#ifdef UA_OUTS
real(ReKi) :: delN
real(ReKi) :: delP
real(ReKi) :: gammaL
real(ReKi) :: gammaD
real(ReKi) :: TransA
#endif

type(AFI_OutputType) :: AFI_interp

#ifdef UA_OUTS
integer :: iOffset
#endif

ErrStat = ErrID_None ! no error has occurred
ErrMsg = ""
Expand Down Expand Up @@ -3392,10 +3404,18 @@ subroutine UA_CalcOutput( i, j, t, u_in, p, x, xd, OtherState, AFInfo, y, misc,
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)

end if ! Switch on UAMod

if (p%UA_OUTS>0) then
if (allocated(y%WriteOutput)) then !bjj: because BEMT uses local variables for UA output, y%WriteOutput is not necessarially allocated. Need to figure out a better solution.
call CalcWriteOutputs()
endif
endif

#ifdef UA_OUTS
iOffset = (i-1)*p%NumOuts + (j-1)*p%nNodesPerBlade*p%NumOuts
if (allocated(y%WriteOutput)) then !bjj: because BEMT uses local variables for UA output, y%WriteOutput is not necessarially allocated. Need to figure out a better solution.
contains

subroutine CalcWriteOutputs()
integer :: iOffset
iOffset = (i-1)*p%NumOuts + (j-1)*p%nNodesPerBlade*p%NumOuts

y%WriteOutput(iOffset+ 1) = u%alpha*R2D
y%WriteOutput(iOffset+ 2) = u%U
Expand Down Expand Up @@ -3502,10 +3522,8 @@ subroutine UA_CalcOutput( i, j, t, u_in, p, x, xd, OtherState, AFInfo, y, misc,
y%WriteOutput(iOffset+45) = KC%alpha_filt_cur*R2D

end if
end if
#endif
end subroutine CalcWriteOutputs

contains
!> Calc Outputs for Boieng-Vertol dynamic stall
!! See BV_DynStall.f95 of CACTUS, and [70], notations kept more or less consistent
subroutine BV_CalcOutput()
Expand All @@ -3522,15 +3540,13 @@ subroutine BV_CalcOutput()
call BV_getAlphas(i, j, u, p, xd, BL_p, AFInfo%RelThickness, alpha_34, alphaE_L, alphaLag_D, adotnorm)
alphaE_D = BV_alphaE_D(adotnorm, alpha_34, alphaLag_D, BL_p, OtherState%activeD(i,j))

#ifdef UA_OUTS
! --- Recompute variables, for temporary output to file only
! Calculate deltas to negative and positive stall angle (delN, and delP)
if (p%UA_OUTS>0) then
call BV_delNP(adotnorm, alpha_34, alphaLag_D, BL_p, OtherState%activeD(i,j), delN, delP)
call BV_getGammas(tc=AFInfo%RelThickness, umach=0.0_ReKi, gammaL=gammaL, gammaD=gammaD)
TransA = BV_TransA(BL_p)
#endif


endif

! --- Cl, _, at effective angle of attack alphaE
if (OtherState%activeL(i,j)) then
Expand Down Expand Up @@ -3595,8 +3611,7 @@ subroutine UA_WriteOutputToFile(t, p, y)
integer :: k

! Generate file outputs
#ifdef UA_OUTS
if (p%unOutFile > 0 .and. allocated(y%WriteOutput)) then
if (p%UA_OUTS==2 .and. p%unOutFile > 0 .and. allocated(y%WriteOutput)) then

write (p%unOutFile,"(F19.6)",ADVANCE='no') t
do k=1,size(y%WriteOutput)
Expand All @@ -3605,7 +3620,6 @@ subroutine UA_WriteOutputToFile(t, p, y)
WRITE (p%unOutFile,'()') ! write the line return

end if
#endif

end subroutine UA_WriteOutputToFile
!==============================================================================
Expand Down
8 changes: 6 additions & 2 deletions modules/aerodyn/src/UnsteadyAero_Driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -99,10 +99,14 @@ program UnsteadyAero_Driver
call driverInputsToUAInitData(dvr%p, dvr%UA_InitInData, dvr%AFI_Params, dvr%AFIndx, errStat, errMsg); call checkError()

! --- Initialize UnsteadyAero (need AFI)
if ( dvr%p%SimMod == 3 ) then
! TODO
dvr%UA_InitInData%UA_OUTS = 1 ! 0=None, 1=Write Outputs, 2=Separate File
endif
call UA_Init( dvr%UA_InitInData, dvr%UA_u(1), dvr%UA_p, dvr%UA_x, dvr%UA_xd, dvr%UA_OtherState, dvr%UA_y, dvr%UA_m, dvr%p%dt, dvr%AFI_Params, dvr%AFIndx, dvr%UA_InitOutData, errStat, errMsg ); call checkError()
if (dvr%UA_p%NumOuts <= 0) then
ErrStat = ErrID_Fatal
ErrMsg = "No outputs have been selected. Rebuild the executable with -DUA_OUTS"
ErrStat = ErrID_Warn
ErrMsg = "No outputs from UA are generated."
call checkError()
end if

Expand Down
6 changes: 4 additions & 2 deletions modules/aerodyn/src/UnsteadyAero_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -41,13 +41,14 @@ typedef ^ ^ Logical
typedef ^ ^ LOGICAL WrSum - .false. - "Write UA AFI parameters to summary file?" -
typedef ^ ^ INTEGER UAOff_innerNode {:} - - "Last node on each blade where UA should be turned off based on span location from blade root (0 if always on)" -
typedef ^ ^ INTEGER UAOff_outerNode {:} - - "First node on each blade where UA should be turned off based on span location from blade tip (>nNodesPerBlade if always on)" -
typedef ^ ^ IntKi UA_OUTS - 0 - "Store write outputs 0=None, 1=WriteOutpus, 2=WriteToFile" -

#
# Define outputs from the initialization routine here:
#
typedef ^ InitOutputType ProgDesc Version - - - "Version structure" -
typedef ^ InitOutputType CHARACTER(19) WriteOutputHdr {:} - - "The is the list of all UA-related output channel header strings (includes all sub-module channels)" -
typedef ^ ^ CHARACTER(19) WriteOutputUnt {:} - - "The is the list of all UA-related output channel unit strings (includes all sub-module channels)" -
typedef ^ InitOutputType CHARACTER(ChanLen) WriteOutputHdr {:} - - "The is the list of all UA-related output channel header strings (includes all sub-module channels)" -
typedef ^ ^ CHARACTER(ChanLen) WriteOutputUnt {:} - - "The is the list of all UA-related output channel unit strings (includes all sub-module channels)" -


# Variables local to the Kelvin Chain:
Expand Down Expand Up @@ -202,6 +203,7 @@ typedef ^ ^ INTEGER
typedef ^ ^ Logical ShedEffect - - - "Include the effect of shed vorticity. If False, the input alpha is assumed to already contain this effect (e.g. vortex methods)" -
typedef ^ ParameterType IntKi lin_nx - 0 - "Number of continuous states for linearization" -
typedef ^ ^ LOGICAL UA_off_forGood {:}{:} - - "logical flag indicating if UA is off for good" -
typedef ^ ^ IntKi UA_OUTS - 0 - "Store write outputs 0=None, 1=WriteOutpus, 2=WriteToFile" -

# ..... Inputs ....................................................................................................................
# Define inputs that are contained on the mesh here:
Expand Down
Loading

0 comments on commit cf21289

Please sign in to comment.