Skip to content

Commit

Permalink
AD bugfix: Segmentation fault with ifx
Browse files Browse the repository at this point in the history
When OLAF was used with the AeroDyn Driver compiled with ifx (IFX) 2023.2.0 20230622 (release only), there would be a segmentation fault when SetInputsForFVW was called.  The root issue was that passing an array of `u` as `(/u/)` doesn't work correctly with this compiler.  So to work around this, the SetInputsForFVW routine was reworked to only operate on a single `u`.

In my opinion this is a hack of a solution to accomodate a compiler bug.
  • Loading branch information
andrew-platt committed Nov 14, 2024
1 parent e7d378b commit 15bafa4
Showing 1 changed file with 26 additions and 26 deletions.
52 changes: 26 additions & 26 deletions modules/aerodyn/src/AeroDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1623,8 +1623,10 @@ subroutine AD_UpdateStates( t, n, u, utimes, p, x, xd, z, OtherState, m, errStat

else ! Call the FVW sub module
! This needs to extract the inputs from the AD data types (mesh) and copy pieces for the FVW module
call SetInputsForFVW(p, u, m, errStat2, errMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
do i=1,size(u)
call SetInputsForFVW(p, u(i), i, m, errStat2, errMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
enddo
! Note: the setup is handled above in the SetInputs routine
call FVW_UpdateStates( t, n, m%FVW_u, utimes, p%FVW, x%FVW, xd%FVW, z%FVW, OtherState%FVW, p%AFI, m%FVW, ErrStat2, ErrMsg2 )
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
Expand Down Expand Up @@ -1696,7 +1698,7 @@ subroutine AD_CalcOutput( t, u, p, x, xd, z, OtherState, y, m, ErrStat, ErrMsg,

if (p%WakeMod == WakeMod_FVW) then
! This needs to extract the inputs from the AD data types (mesh) and copy pieces for the FVW module
call SetInputsForFVW(p, (/u/), m, errStat2, errMsg2)
call SetInputsForFVW(p, u, 1, m, errStat2, errMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
! Calculate Outputs at time t
CALL FVW_CalcOutput( t, m%FVW_u(1), p%FVW, x%FVW, xd%FVW, z%FVW, OtherState%FVW, m%FVW_y, m%FVW, ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -3091,18 +3093,18 @@ subroutine Calculate_MeshOrientation_LiftingLine(p, u, m, thetaBladeNds, toeBlad
end subroutine Calculate_MeshOrientation_LiftingLine
!----------------------------------------------------------------------------------------------------------------------------------
!> This subroutine sets m%FVW_u(indx).
subroutine SetInputsForFVW(p, u, m, errStat, errMsg)
subroutine SetInputsForFVW(p, u, tIndx, m, errStat, errMsg)

type(AD_ParameterType), intent(in ) :: p !< AD parameters
type(AD_InputType), intent(in ) :: u(:) !< AD Inputs at Time
type(AD_InputType), intent(in ) :: u !< AD Inputs at Time
integer(intKi), intent(in ) :: tIndx !< index of m%FVW_u() array
type(AD_MiscVarType), 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

real(R8Ki) :: x_hat_disk(3)
real(R8Ki), allocatable :: thetaBladeNds(:,:)

integer(intKi) :: tIndx
integer(intKi) :: iR ! Loop on rotors
integer(intKi) :: j, k ! loop counter for blades
integer(intKi) :: ErrStat2
Expand All @@ -3113,55 +3115,54 @@ subroutine SetInputsForFVW(p, u, m, errStat, errMsg)
ErrStat = ErrID_None
ErrMsg = ""

do tIndx=1,size(u)
do iR =1, size(p%rotors)
allocate(thetaBladeNds(p%rotors(iR)%NumBlNds, p%rotors(iR)%NumBlades))
! Get disk average values and orientations
! NOTE: needed because it sets m%V_diskAvg and m%V_dot_x, needed by CalcOutput..
call DiskAvgValues(p%rotors(iR), u(tIndx)%rotors(iR), m%rotors(iR), x_hat_disk) ! also sets m%V_diskAvg and m%V_dot_x
call DiskAvgValues(p%rotors(iR), u%rotors(iR), m%rotors(iR), x_hat_disk) ! also sets m%V_diskAvg and m%V_dot_x
if (p%rotors(iR)%AeroProjMod==APM_BEM_NoSweepPitchTwist) then
call Calculate_MeshOrientation_NoSweepPitchTwist(p%rotors(iR),u(tIndx)%rotors(iR), m%rotors(iR), thetaBladeNds,ErrStat=ErrStat2,ErrMsg=ErrMsg2) ! sets m%orientationAnnulus, m%Curve
call Calculate_MeshOrientation_NoSweepPitchTwist(p%rotors(iR),u%rotors(iR), m%rotors(iR), thetaBladeNds,ErrStat=ErrStat2,ErrMsg=ErrMsg2) ! sets m%orientationAnnulus, m%Curve
else if (p%rotors(iR)%AeroProjMod==APM_LiftingLine) then
call Calculate_MeshOrientation_LiftingLine (p%rotors(iR),u(tIndx)%rotors(iR), m%rotors(iR), thetaBladeNds,ErrStat=ErrStat2,ErrMsg=ErrMsg2) ! sets m%orientationAnnulus, m%Curve
call Calculate_MeshOrientation_LiftingLine (p%rotors(iR),u%rotors(iR), m%rotors(iR), thetaBladeNds,ErrStat=ErrStat2,ErrMsg=ErrMsg2) ! sets m%orientationAnnulus, m%Curve
endif
call StorePitchAndAzimuth(p%rotors(iR), u(tIndx)%rotors(iR), m%rotors(iR), ErrStat2, ErrMsg2)
call StorePitchAndAzimuth(p%rotors(iR), u%rotors(iR), m%rotors(iR), ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
if (ErrStat >= AbortErrLev) return

! Rather than use a meshcopy, we will just copy what we need to the WingsMesh
! NOTE: MeshCopy requires the source mesh to be INOUT intent
! NOTE2: If we change the WingsMesh to not be identical to the BladeMotion mesh, add the mapping stuff here.
do k=1,p%rotors(iR)%NumBlades
iW=p%FVW%Bld2Wings(iR,k)

if ( u(tIndx)%rotors(iR)%BladeMotion(k)%nNodes /= m%FVW_u(tIndx)%WingsMesh(iW)%nNodes ) then
if ( u%rotors(iR)%BladeMotion(k)%nNodes /= m%FVW_u(tIndx)%WingsMesh(iW)%nNodes ) then
call SetErrStat(ErrID_Fatal,"WingsMesh contains different number of nodes than the BladeMotion mesh",ErrStat,ErrMsg,RoutineName)
return
endif
m%FVW%W(iW)%PitchAndTwist(:) = thetaBladeNds(:,k) ! local pitch + twist (aerodyanmic + elastic) angle of the jth node in the kth blade
m%FVW_u(tIndx)%WingsMesh(iW)%TranslationDisp = u(tIndx)%rotors(iR)%BladeMotion(k)%TranslationDisp
m%FVW_u(tIndx)%WingsMesh(iW)%Orientation = u(tIndx)%rotors(iR)%BladeMotion(k)%Orientation
m%FVW_u(tIndx)%WingsMesh(iW)%TranslationVel = u(tIndx)%rotors(iR)%BladeMotion(k)%TranslationVel
m%FVW_u(tIndx)%rotors(iR)%HubPosition = u(tIndx)%rotors(iR)%HubMotion%Position(:,1) + u(tIndx)%rotors(iR)%HubMotion%TranslationDisp(:,1)
m%FVW_u(tIndx)%rotors(iR)%HubOrientation = u(tIndx)%rotors(iR)%HubMotion%Orientation(:,:,1)

m%FVW_u(tIndx)%WingsMesh(iW)%TranslationDisp = u%rotors(iR)%BladeMotion(k)%TranslationDisp
m%FVW_u(tIndx)%WingsMesh(iW)%Orientation = u%rotors(iR)%BladeMotion(k)%Orientation
m%FVW_u(tIndx)%WingsMesh(iW)%TranslationVel = u%rotors(iR)%BladeMotion(k)%TranslationVel
m%FVW_u(tIndx)%rotors(iR)%HubPosition = u%rotors(iR)%HubMotion%Position(:,1) + u%rotors(iR)%HubMotion%TranslationDisp(:,1)
m%FVW_u(tIndx)%rotors(iR)%HubOrientation = u%rotors(iR)%HubMotion%Orientation(:,:,1)
! Inputs for dynamic stall (see SetInputsForBEMT)
do j=1,p%rotors(iR)%NumBlNds
! inputs for CUA, section pitch/torsion rate
m%FVW_u(tIndx)%W(iW)%omega_z(j) = dot_product( u(tIndx)%rotors(iR)%BladeMotion(k)%RotationVel( :,j), m%rotors(iR)%orientationAnnulus(3,:,j,k) ) ! rotation of no-sweep-pitch coordinate system around z of the jth node in the kth blade
m%FVW_u(tIndx)%W(iW)%omega_z(j) = dot_product( u%rotors(iR)%BladeMotion(k)%RotationVel( :,j), m%rotors(iR)%orientationAnnulus(3,:,j,k) ) ! rotation of no-sweep-pitch coordinate system around z of the jth node in the kth blade
end do !j=nodes
enddo ! k blades
if (allocated(thetaBladeNds)) deallocate(thetaBladeNds)
enddo ! iR, rotors

if (ALLOCATED(m%FVW_u(tIndx)%V_wind)) then
m%FVW_u(tIndx)%V_wind = u(tIndx)%InflowWakeVel
m%FVW_u(tIndx)%V_wind = u%InflowWakeVel
! Applying tower shadow to V_wind based on r_wind positions
! NOTE: m%DisturbedInflow also contains tower shadow and we need it for CalcOutput
if (p%FVW%TwrShadowOnWake) then
do iR =1, size(p%rotors)
if (p%rotors(iR)%TwrPotent /= TwrPotent_none .or. p%rotors(iR)%TwrShadow /= TwrShadow_none) then
call TwrInflArray( p%rotors(iR), u(tIndx)%rotors(iR), m%rotors(iR), m%FVW%r_wind, m%FVW_u(tIndx)%V_wind, ErrStat2, ErrMsg2 )
call TwrInflArray( p%rotors(iR), u%rotors(iR), m%rotors(iR), m%FVW%r_wind, m%FVW_u(tIndx)%V_wind, ErrStat2, ErrMsg2 )
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
if (ErrStat >= AbortErrLev) return
endif
Expand All @@ -3170,14 +3171,13 @@ 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), p, u(tIndx)%rotors(iR), m%rotors(iR), errStat2, errMsg2)
call SetDisturbedInflow(p%rotors(iR), p, u%rotors(iR), m%rotors(iR), errStat2, errMsg2)
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
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)
enddo
enddo
enddo

end subroutine SetInputsForFVW
!----------------------------------------------------------------------------------------------------------------------------------
Expand Down

0 comments on commit 15bafa4

Please sign in to comment.