Skip to content

Commit

Permalink
Remove unused variables + replace norm2 with TwoNorm
Browse files Browse the repository at this point in the history
- `norm2` is not standard Fortran 2003, so produced warning on build.
  • Loading branch information
bjonkman committed Mar 7, 2024
1 parent 37d2cfe commit 5159a51
Showing 1 changed file with 5 additions and 35 deletions.
40 changes: 5 additions & 35 deletions modules/openfast-library/src/FAST_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,6 @@ SUBROUTINE FAST_InitializeAll( t_initial, p_FAST, y_FAST, m_FAST, ED, BD, SrvD,
INTEGER(IntKi) :: IceDim ! dimension we're pre-allocating for number of IceDyn legs/instances
INTEGER(IntKi) :: I ! generic loop counter
INTEGER(IntKi) :: k ! blade loop counter
INTEGER(IntKi) :: nNodes ! temp var for ExtInfw coupling
logical :: CallStart

REAL(R8Ki) :: theta(3) ! angles for hub orientation matrix for aeromaps
Expand Down Expand Up @@ -1626,7 +1625,7 @@ SUBROUTINE FAST_InitializeAll( t_initial, p_FAST, y_FAST, m_FAST, ED, BD, SrvD,
! Initialize data for VTK output
! -------------------------------------------------------------------------
if ( p_FAST%WrVTK > VTK_None ) then
call SetVTKParameters(p_FAST, Init%OutData_ED, Init%OutData_AD, Init%InData_SeaSt, Init%OutData_SeaSt, Init%OutData_HD, ED, BD, AD, HD, ErrStat2, ErrMsg2)
call SetVTKParameters(p_FAST, Init%OutData_ED, Init%OutData_AD, Init%OutData_SeaSt, Init%OutData_HD, ED, BD, AD, HD, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
end if

Expand Down Expand Up @@ -3938,12 +3937,11 @@ end subroutine cleanup
END SUBROUTINE FAST_ReadSteadyStateFile
!----------------------------------------------------------------------------------------------------------------------------------
!> This subroutine sets up the information needed for plotting VTK surfaces.
SUBROUTINE SetVTKParameters(p_FAST, InitOutData_ED, InitOutData_AD, InitInData_SeaSt, InitOutData_SeaSt, InitOutData_HD, ED, BD, AD, HD, ErrStat, ErrMsg)
SUBROUTINE SetVTKParameters(p_FAST, InitOutData_ED, InitOutData_AD, InitOutData_SeaSt, InitOutData_HD, ED, BD, AD, HD, ErrStat, ErrMsg)

TYPE(FAST_ParameterType), INTENT(INOUT) :: p_FAST !< The parameters of the glue code
TYPE(ED_InitOutputType), INTENT(IN ) :: InitOutData_ED !< The initialization output from structural dynamics module
TYPE(AD_InitOutputType), INTENT(INOUT) :: InitOutData_AD !< The initialization output from AeroDyn
TYPE(SeaSt_InitInputType), INTENT(INOUT) :: InitInData_SeaSt !< The initialization input to SeaState
TYPE(SeaSt_InitOutputType), INTENT(INOUT) :: InitOutData_SeaSt !< The initialization output from SeaState
TYPE(HydroDyn_InitOutputType),INTENT(INOUT) :: InitOutData_HD !< The initialization output from HydroDyn
TYPE(ElastoDyn_Data), TARGET, INTENT(IN ) :: ED !< ElastoDyn data
Expand Down Expand Up @@ -4520,7 +4518,7 @@ SUBROUTINE ExtLd_SetInitInput(InitInData_ExtLd, InitOutData_ED, y_ED, InitOutDat
do k=1,InitInData_ExtLd%NumBlades
InitInData_ExtLd%BldRloc(1,k) = 0.0
do j = 2, InitInData_ExtLd%NumBldNodes(k)
InitInData_ExtLd%BldRloc(j,k) = InitInData_ExtLd%BldRloc(j-1,k) + norm2(InitInData_ExtLd%BldPos(:,j,k) - InitInData_ExtLd%BldPos(:,j-1,k))
InitInData_ExtLd%BldRloc(j,k) = InitInData_ExtLd%BldRloc(j-1,k) + TwoNorm(InitInData_ExtLd%BldPos(:,j,k) - InitInData_ExtLd%BldPos(:,j-1,k))
end do
end do

Expand Down Expand Up @@ -4582,7 +4580,7 @@ SUBROUTINE ExtLd_SetInitInput(InitInData_ExtLd, InitOutData_ED, y_ED, InitOutDat

InitInData_ExtLd%TwrHloc(1) = 0.0
do j = 2, InitInData_ExtLd%NumTwrNds
InitInData_ExtLd%TwrHloc(j) = InitInData_ExtLd%TwrHloc(j-1) + norm2(InitInData_ExtLd%TwrPos(:,j) - InitInData_ExtLd%TwrPos(:,j-1))
InitInData_ExtLd%TwrHloc(j) = InitInData_ExtLd%TwrHloc(j-1) + TwoNorm(InitInData_ExtLd%TwrPos(:,j) - InitInData_ExtLd%TwrPos(:,j-1))
end do
END IF

Expand Down Expand Up @@ -6204,9 +6202,6 @@ SUBROUTINE FAST_Reset_SubStep(t_initial, n_t_global, n_timesteps, p_FAST, y_FAST
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None

! local variables
INTEGER(IntKi) :: j_pc ! predictor-corrector loop counter
INTEGER(IntKi) :: NumCorrections ! number of corrections for this time step

INTEGER(IntKi) :: i, j, k ! generic loop counters
REAL(DbKi) :: t_global ! the time to which states, inputs and outputs are reset
INTEGER(IntKi) :: old_avrSwap1 ! previous value of avrSwap(1) !hack for Bladed DLL checkpoint/restore
Expand Down Expand Up @@ -6792,9 +6787,6 @@ SUBROUTINE FAST_Store_SubStep(t_initial, n_t_global, p_FAST, y_FAST, m_FAST, ED,
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None

! local variables
INTEGER(IntKi) :: j_pc ! predictor-corrector loop counter
INTEGER(IntKi) :: NumCorrections ! number of corrections for this time step

INTEGER(IntKi) :: i, j, k ! generic loop counters
REAL(DbKi) :: t_global ! the time to which states, inputs and outputs are reset
INTEGER(IntKi) :: old_avrSwap1 ! previous value of avrSwap(1) !hack for Bladed DLL checkpoint/restore
Expand Down Expand Up @@ -7371,23 +7363,12 @@ SUBROUTINE FAST_Solution(t_initial, n_t_global, p_FAST, y_FAST, m_FAST, ED, BD,
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None

! local variables
REAL(DbKi) :: t_global_next ! next simulation time (m_FAST%t_global + p_FAST%dt)
INTEGER(IntKi) :: n_t_global_next ! n_t_global + 1
INTEGER(IntKi) :: j_pc ! predictor-corrector loop counter
INTEGER(IntKi) :: NumCorrections ! number of corrections for this time step
INTEGER(IntKi), parameter :: MaxCorrections = 20 ! maximum number of corrections allowed
LOGICAL :: WriteThisStep ! Whether WriteOutput values will be printed

INTEGER(IntKi) :: I, k ! generic loop counters

!REAL(ReKi) :: ControlInputGuess ! value of controller inputs


INTEGER(IntKi) :: ErrStat2
CHARACTER(ErrMsgLen) :: ErrMsg2
CHARACTER(*), PARAMETER :: RoutineName = 'FAST_Solution'


ErrStat = ErrID_None
ErrMsg = ""

Expand Down Expand Up @@ -7485,11 +7466,6 @@ SUBROUTINE FAST_Prework(t_initial, n_t_global, p_FAST, y_FAST, m_FAST, ED, BD, S
! local variables
INTEGER(IntKi) :: n_t_global_next ! n_t_global + 1
REAL(DbKi) :: t_global_next ! next simulation time (m_FAST%t_global + p_FAST%dt)
INTEGER(IntKi) :: j_pc ! predictor-corrector loop counter
INTEGER(IntKi) :: NumCorrections ! number of corrections for this time step

INTEGER(IntKi) :: I, k ! generic loop counters


INTEGER(IntKi) :: ErrStat2
CHARACTER(ErrMsgLen) :: ErrMsg2
Expand Down Expand Up @@ -7599,8 +7575,7 @@ SUBROUTINE FAST_UpdateStates(t_initial, n_t_global, p_FAST, y_FAST, m_FAST, ED,
INTEGER(IntKi), parameter :: MaxCorrections = 20 ! maximum number of corrections allowed
LOGICAL :: WriteThisStep ! Whether WriteOutput values will be printed

INTEGER(IntKi) :: I, k ! generic loop counters

!REAL(ReKi) :: ControlInputGuess ! value of controller inputs

INTEGER(IntKi) :: ErrStat2
CHARACTER(ErrMsgLen) :: ErrMsg2
Expand Down Expand Up @@ -7747,12 +7722,8 @@ SUBROUTINE FAST_AdvanceToNextTimeStep(t_initial, n_t_global, p_FAST, y_FAST, m_F

! local variables
REAL(DbKi) :: t_global_next ! next simulation time (m_FAST%t_global + p_FAST%dt)
INTEGER(IntKi) :: j_pc ! predictor-corrector loop counter
INTEGER(IntKi) :: NumCorrections ! number of corrections for this time step

INTEGER(IntKi) :: I, k ! generic loop counters


INTEGER(IntKi) :: ErrStat2
CHARACTER(ErrMsgLen) :: ErrMsg2
CHARACTER(*), PARAMETER :: RoutineName = 'FAST_AdvanceToNextTimeStep'
Expand Down Expand Up @@ -8008,7 +7979,6 @@ SUBROUTINE FAST_WriteOutput(t_initial, n_t_global, p_FAST, y_FAST, m_FAST, ED, B
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None

! local variables
INTEGER(IntKi) :: I, k ! generic loop counters
REAL(DbKi) :: t_global ! this simulation time (m_FAST%t_global + p_FAST%dt)
INTEGER(IntKi) :: ErrStat2
CHARACTER(ErrMsgLen) :: ErrMsg2
Expand Down

0 comments on commit 5159a51

Please sign in to comment.