Skip to content

Commit

Permalink
Address comments in PR #2283
Browse files Browse the repository at this point in the history
  • Loading branch information
bjonkman committed Aug 15, 2024
1 parent b9a39a6 commit 1dbbbbd
Show file tree
Hide file tree
Showing 4 changed files with 72 additions and 66 deletions.
62 changes: 5 additions & 57 deletions modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1394,9 +1394,12 @@ SUBROUTINE ReadBladeInputs ( ADBlFile, BladeKInputFileData, AeroProjMod, UnEc, c
INTEGER, PARAMETER :: MaxCols = 10
CHARACTER(NWTC_SizeOfNumWord*(MaxCols+1)) :: Line
INTEGER(IntKi) :: Indx(MaxCols)
CHARACTER(8), PARAMETER :: AvailableChanNames(MaxCols) = (/'BLSPN ', 'BLCRVAC ','BLSWPAC ','BLCRVANG','BLTWIST ','BLCHORD ', 'BLAFID ', 'BLCB ', 'BLCENBN ','BLCENBT ' /) ! in upper case only
LOGICAL, PARAMETER :: RequiredChanNames( MaxCols) = (/.true. , .true. ,.true. ,.false. ,.true. ,.true. , .true. , .false. , .false. ,.false. /)

CHARACTER(*), PARAMETER :: RoutineName = 'ReadBladeInputs'


ErrStat = ErrID_None
ErrMsg = ""
UnIn = -1
Expand Down Expand Up @@ -1482,7 +1485,7 @@ SUBROUTINE ReadBladeInputs ( ADBlFile, BladeKInputFileData, AeroProjMod, UnEc, c


! figure out what columns are specified in this file and in what order:
CALL GetInputColumnIndex(Line, Indx, ErrStat2, ErrMsg2)
CALL GetInputColumnIndex(MaxCols, AvailableChanNames, RequiredChanNames, Line, Indx, ErrStat2, ErrMsg2)
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
IF ( ErrStat >= AbortErrLev ) THEN
CALL Cleanup()
Expand Down Expand Up @@ -1570,7 +1573,7 @@ SUBROUTINE ConvertLineToCols(Line, i, Indx, BladeKInputFileData, ErrStat, ErrMsg

IOS = 0 ! initialize in case we don't read all of the columns

! Note: See order of variable AvailableChanNames in subroutine GetInputColumnIndex() for these variables indices
! Note: See order of variable AvailableChanNames in subroutine ReadBladeInputs() for these variables indices
! Also, we have checked that Indx is non zero and less than MaxCols for each of the required words
c=Indx( 1); READ( Words(c), *, IOStat=IOS(c) ) BladeKInputFileData%BlSpn(I)
c=Indx( 2); READ( Words(c), *, IOStat=IOS(c) ) BladeKInputFileData%BlCrvAC(I)
Expand Down Expand Up @@ -1605,61 +1608,6 @@ SUBROUTINE ConvertLineToCols(Line, i, Indx, BladeKInputFileData, ErrStat, ErrMsg
END IF

END SUBROUTINE ConvertLineToCols
!----------------------------------------------------------------------------------------------------------------------------------
SUBROUTINE GetInputColumnIndex(HeaderLine, Indx, ErrStat, ErrMsg)

CHARACTER(*), INTENT(IN ) :: HeaderLine
INTEGER(IntKi), INTENT(INOUT) :: Indx(:)
INTEGER(IntKi), INTENT( OUT) :: ErrStat
CHARACTER(*), INTENT( OUT) :: ErrMsg


CHARACTER(8), PARAMETER :: AvailableChanNames(10) = (/'BLSPN ', 'BLCRVAC ','BLSWPAC ','BLCRVANG','BLTWIST ','BLCHORD ', 'BLAFID ', 'BLCB ', 'BLCENBN ','BLCENBT ' /) ! in upper case only
LOGICAL, PARAMETER :: RequiredChanNames( 10) = (/.true. , .true. ,.true. ,.false. ,.true. ,.true. , .true. , .false. , .false. ,.false. /)
CHARACTER(ChanLen) :: Words(SIZE(AvailableChanNames))
INTEGER(IntKi) :: i ! loop counter
INTEGER(IntKi) :: j ! loop counter
INTEGER(IntKi) :: FirstCheck
INTEGER(IntKi) :: NumFound

ErrStat = ErrID_None
ErrMsg = ""

CALL GetWords ( HeaderLine, Words, SIZE(AvailableChanNames), NumFound )

DO j = 1,NumFound
CALL Conv2UC ( Words(j) )

! stop reading any more headers if this word starts with a comment character (indicating that the columns aren't in the table)
IF ( INDEX( CommChars, Words(j)(1:1) ) > 0 ) THEN
NumFound = j - 1
EXIT
END IF
END DO

Indx = -1 ! initialize all values to be "not found"

FirstCheck = 1
DO i = 1,SIZE(Indx)
DO j = FirstCheck,NumFound
IF ( TRIM(AvailableChanNames(i)) == TRIM(Words(j)) ) THEN
Indx(I) = j
IF (j == FirstCheck + 1) FirstCheck = FirstCheck + 1 ! attempt to make this loop a little faster without assuming anything about the order of the words found
CYCLE
END IF
END DO
END DO

! check that the required columns are in the file:
DO i = 1,SIZE(Indx)
IF (Indx(i) < 1 .and. RequiredChanNames(i)) THEN
ErrStat = ErrID_Fatal
ErrMsg = TRIM(AvailableChanNames(i))//" , a required input, was not found in the blade input file."
RETURN
END IF
END DO

END SUBROUTINE GetInputColumnIndex

!----------------------------------------------------------------------------------------------------------------------------------
!> Read Tail Fin inputs
Expand Down
2 changes: 1 addition & 1 deletion modules/aerodyn/src/FVW.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1573,7 +1573,7 @@ subroutine UA_Init_Wrapper(AFInfo, InitInp, interval, p, x, xd, OtherState, m, E
integer(IntKi), intent( out) :: ErrStat !< Error status of the operation
character(*), intent( out) :: ErrMsg !< Error message if ErrStat /= ErrID_None

integer(IntKi), parameter :: NumBladesPerWing = 1 !bjj why are we using this number?
integer(IntKi), parameter :: NumBladesPerWing = 1 ! UA is called separately for each wing (i.e., blade). In BEMT, UA is called for all blades on a single rotor.
!
type(UA_InitOutputType):: InitOutData_UA
integer :: i,iW
Expand Down
14 changes: 7 additions & 7 deletions modules/aerodyn/src/UnsteadyAero.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2705,6 +2705,9 @@ subroutine UA_CalcContStateDeriv( i, j, t, u_in, p, x, OtherState, AFInfo, m, dx
BL_p%T_f0 = BL_p%T_f0 * Tu ! Emmanuel wants a factor of 2 here to match HAWC2, but we don't want that factor for Bladed comparisons
BL_p%T_p = BL_p%T_p * Tu

TuOmega = Tu * u%omega
TuOmega = MIN( MAX(TuOmega, -MaxTuOmega), MaxTuOmega)

! calculate fs_aF (stored in AFI_interp%f_st):
! find alphaF where FullyAttached(alphaF) = x(3)
alphaF = Get_alphaF(p, u, x, BL_p, alpha_34, alphaE)
Expand Down Expand Up @@ -2736,13 +2739,13 @@ subroutine UA_CalcContStateDeriv( i, j, t, u_in, p, x, OtherState, AFInfo, m, dx

if (p%UAMod == UA_HGM) then
call AddOrSub2Pi(BL_p%alpha0, alphaE)
Clp = BL_p%c_lalpha * (alphaE - BL_p%alpha0) + pi * Tu * u%omega ! Eq. 13
dxdt%x(3) = -1.0_R8Ki / BL_p%T_p * x%x(3) + 1.0_ReKi / BL_p%T_p * Clp ! Eq. 10 [40]
dxdt%x(4) = -1.0_R8Ki / BL_p%T_f0 * x4 + 1.0_ReKi / BL_p%T_f0 * AFI_AlphaF%f_st ! Eq. 11 [40]
Clp = BL_p%c_lalpha * (alphaE - BL_p%alpha0) + pi * TuOmega ! Eq. 13
dxdt%x(3) = ( Clp - x%x(3) ) / BL_p%T_p ! Eq. 10 [40]
dxdt%x(4) = ( AFI_AlphaF%f_st - x4 ) / BL_p%T_f0 ! Eq. 11 [40]
dxdt%x(5) = 0.0_R8Ki

elseif (p%UAMod == UA_OYE) then
dxdt%x(4) = -1.0_R8Ki / BL_p%T_f0 * x4 + 1.0_ReKi / BL_p%T_f0 * AFI_AlphaF%f_st
dxdt%x(4) = ( AFI_AlphaF%f_st - x4 ) / BL_p%T_f0
dxdt%x(1) = 0.0_R8Ki
dxdt%x(2) = 0.0_R8Ki
dxdt%x(3) = 0.0_R8Ki
Expand All @@ -2754,9 +2757,6 @@ subroutine UA_CalcContStateDeriv( i, j, t, u_in, p, x, OtherState, AFInfo, m, dx
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
if (ErrStat >= AbortErrLev) return

TuOmega = Tu * u%omega
TuOmega = MIN( MAX(TuOmega, -MaxTuOmega), MaxTuOmega)

Clp = AFI_AlphaE%FullyAttached + pi * TuOmega ! Eq. 13 (this is really Cnp)
dxdt%x(3) = ( Clp - x%x(3) ) / BL_p%T_p
dxdt%x(4) = ( AFI_AlphaF%f_st - x4 ) / BL_p%T_f0
Expand Down
60 changes: 59 additions & 1 deletion modules/nwtc-library/src/NWTC_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1892,7 +1892,6 @@ FUNCTION GetErrStr ( ErrID )


END FUNCTION GetErrStr

!=======================================================================
!> This function extracts the Name field from the ProgDesc data type
! and return it.
Expand Down Expand Up @@ -2134,6 +2133,65 @@ SUBROUTINE GetWords ( Line, Words, NumWords, NumFound )
RETURN
END SUBROUTINE GetWords
!=======================================================================
!> This subroutine is used to compare a header line (`HeaderLine`) with a list of column names.
!! It searches for each possible column name (AvailableChanName) and returns an index array indicating which
!! order the columns are listed in the file (this allows columns to be entered in different orders or for
!! some columns to be missing. It returns an error if any of the required channels are missing.
SUBROUTINE GetInputColumnIndex(MaxCols, AvailableChanNames, RequiredChanNames, HeaderLine, Indx, ErrStat, ErrMsg)

INTEGER(IntKi), INTENT(IN ) :: MaxCols !< maximum number of columns that should be in the input file
CHARACTER(*), INTENT(IN ) :: AvailableChanNames(MaxCols) !< list of column headers, THESE SHOULD BE IN UPPER CASE
LOGICAL, INTENT(IN ) :: RequiredChanNames( MaxCols) !< T/F corresponding to channel names to determine if these channels should be required
CHARACTER(*), INTENT(IN ) :: HeaderLine !< line of text to be read
INTEGER(IntKi), INTENT(INOUT) :: Indx(MaxCols) !< index relating upper-case column names found in header line with AvailableChanNames
INTEGER(IntKi), INTENT( OUT) :: ErrStat !< returns a fatal error if a required channel name isn't found in HeaderLine
CHARACTER(*), INTENT( OUT) :: ErrMsg !< returns message about which column is missing

CHARACTER(ChanLen) :: Words(MaxCols)
INTEGER(IntKi) :: i ! loop counter
INTEGER(IntKi) :: j ! loop counter
INTEGER(IntKi) :: FirstCheck
INTEGER(IntKi) :: NumFound

ErrStat = ErrID_None
ErrMsg = ""

CALL GetWords ( HeaderLine, Words, MaxCols, NumFound )

DO j = 1,NumFound
CALL Conv2UC ( Words(j) )

! stop reading any more headers if this word starts with a comment character (indicating that the columns aren't in the table)
IF ( INDEX( CommChars, Words(j)(1:1) ) > 0 ) THEN
NumFound = j - 1
EXIT
END IF
END DO

Indx = -1 ! initialize all values to be "not found"

FirstCheck = 1
DO i = 1,SIZE(Indx)
DO j = FirstCheck,NumFound
IF ( TRIM(AvailableChanNames(i)) == TRIM(Words(j)) ) THEN
Indx(I) = j
IF (j == FirstCheck + 1) FirstCheck = FirstCheck + 1 ! attempt to make this loop a little faster without assuming anything about the order of the words found
CYCLE
END IF
END DO
END DO

! check that the required columns are in the file:
DO i = 1,SIZE(Indx)
IF (Indx(i) < 1 .and. RequiredChanNames(i)) THEN
ErrStat = ErrID_Fatal
ErrMsg = TRIM(AvailableChanNames(i))//" , a required input, was not found in the line."
RETURN
END IF
END DO

END SUBROUTINE GetInputColumnIndex
!=======================================================================
!> This routine converts an ASCII array of integers into an equivalent string
!! (character array). This routine is the inverse of the Str2IntAry() (nwtc_io::str2intary) routine.
SUBROUTINE IntAry2Str( IntAry, Str, ErrStat, ErrMsg )
Expand Down

0 comments on commit 1dbbbbd

Please sign in to comment.