Skip to content

Commit

Permalink
AD15: move wind velocity storage to miscvar in type RotInflow
Browse files Browse the repository at this point in the history
- Add extrap-interp routine in registry for AD_RotInflowType (temporary for testing)
- Add RotInflow type to AD, and add this into misc vars.  This, with the above, should produce exactly the same results as before.

This is almost working locally, but fails on one test.  Hoping this is just numerics that work on GH (going to test).
  • Loading branch information
andrew-platt committed Nov 17, 2023
1 parent de60b1a commit ce100ad
Show file tree
Hide file tree
Showing 9 changed files with 1,239 additions and 775 deletions.
480 changes: 281 additions & 199 deletions modules/aerodyn/src/AeroDyn.f90

Large diffs are not rendered by default.

33 changes: 17 additions & 16 deletions modules/aerodyn/src/AeroDyn_AllBldNdOuts_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -264,7 +264,7 @@ END SUBROUTINE AllBldNdOuts_InitOut
!! NOTE: the equations here came from the output section of AeroDyn_IO.f90. If anything changes in there, it needs to be reflected
!! here.

SUBROUTINE Calc_WriteAllBldNdOutput( p, p_AD, u, m, m_AD, x, y, OtherState, Indx, iRot, ErrStat, ErrMsg )
SUBROUTINE Calc_WriteAllBldNdOutput( p, p_AD, u, m, m_AD, x, y, OtherState, RotInflow, Indx, iRot, ErrStat, ErrMsg )
TYPE(RotParameterType), INTENT(IN ) :: p ! The rotor parameters
TYPE(AD_ParameterType),target,INTENT(IN ) :: p_AD ! The module parameters
TYPE(RotInputType), target, INTENT(IN ) :: u ! inputs
Expand All @@ -273,6 +273,7 @@ SUBROUTINE Calc_WriteAllBldNdOutput( p, p_AD, u, m, m_AD, x, y, OtherState, Indx
TYPE(RotContinuousStateType), INTENT(IN ) :: x ! rotor Continuous states
TYPE(RotOutputType), INTENT(INOUT) :: y ! outputs (updates y%WriteOutput)
TYPE(RotOtherStateType), INTENT(IN ) :: OtherState ! other states
TYPE(RotInflowType), INTENT(IN ) :: RotInflow ! other states%RotInflow(iRot)
INTEGER, INTENT(IN ) :: Indx ! index into m%BEMT_u(Indx) array; 1=t and 2=t+dt (but not checked here)
INTEGER, INTENT(IN ) :: iRot ! Rotor index, needed for OLAF
INTEGER(IntKi), INTENT( OUT) :: ErrStat ! The error status code
Expand Down Expand Up @@ -335,26 +336,26 @@ SUBROUTINE Calc_WriteAllBldNdOutput( p, p_AD, u, m, m_AD, x, y, OtherState, Indx
CASE (0 ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = 0.0_ReKi; iOut = iOut + 1; enddo;enddo

! ***** Undisturbed wind velocity in inertial, polar, local and airfoil systems*****
CASE( BldNd_VUndxi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = u%Bld(iB)%InflowOnBlade(1,iNd); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = u%Bld(iB)%InflowOnBlade(2,iNd); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = u%Bld(iB)%InflowOnBlade(3,iNd); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndxi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = RotInflow%Bld(iB)%InflowOnBlade(1,iNd); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = RotInflow%Bld(iB)%InflowOnBlade(2,iNd); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzi ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = RotInflow%Bld(iB)%InflowOnBlade(3,iNd); iOut = iOut + 1; enddo;enddo

CASE( BldNd_VUndxp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_pi(1,:,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_pi(2,:,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_pi(3,:,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndxp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_pi(1,:,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_pi(2,:,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzp ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_pi(3,:,iB) ); iOut = iOut + 1; enddo;enddo

CASE( BldNd_VUndxl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_li(1,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_li(2,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_li(3,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndxl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_li(1,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndyl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_li(2,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndzl ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_li(3,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo

CASE( BldNd_VUndxa ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(1,:,iNd) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndya ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(2,:,iNd) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndza ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(3,:,iNd) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndxa ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(1,:,iNd) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndya ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(2,:,iNd) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndza ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), u%BladeMotion(iB)%Orientation(3,:,iNd) ); iOut = iOut + 1; enddo;enddo

! TODO: deprecate this
CASE( BldNd_VUndx ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_wi(1,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndy ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_wi(2,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndz ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( u%Bld(iB)%InflowOnBlade(:,iNd), R_wi(3,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndx ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_wi(1,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndy ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_wi(2,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo
CASE( BldNd_VUndz ); do iB=1,nB; do iNd=1,nNd; y%WriteOutput(iOut) = dot_product( RotInflow%Bld(iB)%InflowOnBlade(:,iNd), R_wi(3,:,iNd,iB) ); iOut = iOut + 1; enddo;enddo


! ***** Disturbed wind velocity in inertial, polar, local and airfoil systems*****
Expand Down
7 changes: 4 additions & 3 deletions modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,11 +83,12 @@ END FUNCTION Calc_Chi0


!----------------------------------------------------------------------------------------------------------------------------------
SUBROUTINE Calc_WriteOutput( p, p_AD, u, x, m, m_AD, y, OtherState, xd, indx, iRot, ErrStat, ErrMsg )
SUBROUTINE Calc_WriteOutput( p, p_AD, u, RotInflow, x, m, m_AD, y, OtherState, xd, indx, iRot, ErrStat, ErrMsg )

TYPE(RotParameterType), INTENT(IN ) :: p ! The rotor parameters
TYPE(AD_ParameterType), INTENT(IN ) :: p_AD ! The module parameters
TYPE(RotInputType), INTENT(IN ) :: u ! inputs
TYPE(RotInflowType), INTENT(IN ) :: RotInflow ! other states%RotInflow at t (for DBEMT and UA)
TYPE(RotContinuousStateType), INTENT(IN ) :: x !< Continuous states at t
TYPE(RotMiscVarType), INTENT(INOUT) :: m ! misc variables
TYPE(AD_MiscVarType), INTENT(INOUT) :: m_AD ! misc variables
Expand Down Expand Up @@ -162,7 +163,7 @@ subroutine Calc_WriteOutput_AD()
do beta=1,p%NTwOuts
j = p%TwOutNd(beta)

tmp = matmul( u%TowerMotion%Orientation(:,:,j) , u%InflowOnTower(:,j) )
tmp = matmul( u%TowerMotion%Orientation(:,:,j) , RotInflow%InflowOnTower(:,j) )
m%AllOuts( TwNVUnd(:,beta) ) = tmp

tmp = matmul( u%TowerMotion%Orientation(:,:,j) , u%TowerMotion%TranslationVel(:,j) )
Expand Down Expand Up @@ -220,7 +221,7 @@ subroutine Calc_WriteOutput_AD()
do beta=1,p%NBlOuts
j=p%BlOutNd(beta)

tmp = matmul( m%orientationAnnulus(:,:,j,k), u%Bld(k)%InflowOnBlade(:,j) )
tmp = matmul( m%orientationAnnulus(:,:,j,k), RotInflow%Bld(k)%InflowOnBlade(:,j) )
m%AllOuts( BNVUndx(beta,k) ) = tmp(1)
m%AllOuts( BNVUndy(beta,k) ) = tmp(2)
m%AllOuts( BNVUndz(beta,k) ) = tmp(3)
Expand Down
2 changes: 1 addition & 1 deletion modules/aerodyn/src/AeroDyn_Inflow.f90
Original file line number Diff line number Diff line change
Expand Up @@ -303,7 +303,7 @@ subroutine ADI_CalcOutput(t, u, p, x, xd, z, OtherState, y, m, errStat, errMsg)

if (p%storeHHVel) then
do iWT = 1, size(u%AD%rotors)
y%HHVel(:,iWT) = u%AD%rotors(iWT)%InflowOnHub(:,1)
y%HHVel(:,iWT) = m%AD%Inflow(1)%RotInflow(iWT)%InflowOnHub(:,1)
end do
endif

Expand Down
25 changes: 15 additions & 10 deletions modules/aerodyn/src/AeroDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -328,6 +328,21 @@ typedef ^ MiscVarType ReKi WindPos {:}{:} - - "XYZ coordinates to que
typedef ^ MiscVarType ReKi WindVel {:}{:} - - "XYZ components of wind velocity" -
typedef ^ MiscVarType ReKi WindAcc {:}{:} - - "XYZ components of wind acceleration" -

# Inflow data storage
typedef ^ BldInflowType ReKi InflowOnBlade {:}{:} - - "U,V,W at nodes on each blade (note if we change the requirement that NumNodes is the same for each blade, this will need to change)" m/s
typedef ^ BldInflowType ReKi AccelOnBlade {:}{:} - - "Wind acceleration at nodes on each blade (note if we change the requirement that NumNodes is the same for each blade, this will need to change)" m/s
typedef ^ RotInflowType BldInflowType Bld {:} - - "Blade Inputs" -
typedef ^ RotInflowType ReKi InflowOnTower {:}{:} - - "U,V,W at nodes on the tower" m/s
typedef ^ RotInflowType ReKi AccelOnTower {:}{:} - - "Wind acceleration at nodes on the tower" m/s
typedef ^ RotInflowType ReKi InflowOnHub {3}{1} - - "U,V,W at hub" m/s
typedef ^ RotInflowType ReKi InflowOnNacelle {3}{1} - - "U,V,W at nacelle" m/s
typedef ^ RotInflowType ReKi InflowOnTailFin {3}{1} - - "U,V,W at tailfin" m/s
typedef ^ RotInflowType ReKi AvgDiskVel {3} - 0.0 "disk-averaged U,V,W" m/s
typedef ^ AD_InflowType ReKi InflowWakeVel {:}{:} - - "U,V,W at wake points" m/s
typedef ^ AD_InflowType RotInflowType RotInflow {:} - - "Inflow on rotor" -
typedef ^ MiscVarType AD_InflowType Inflow {:} - - "Inflow storage (size of u for history of inputs)" -


# ..... Parameters ................................................................................................................
# Define parameters here:

Expand Down Expand Up @@ -416,8 +431,6 @@ typedef ^ ParameterType FlowFieldType *FlowField - - - "Pointer of Inf


# ..... Inputs ....................................................................................................................
typedef ^ BldInputType ReKi InflowOnBlade {:}{:} - - "U,V,W at nodes on each blade (note if we change the requirement that NumNodes is the same for each blade, this will need to change)" m/s
typedef ^ BldInputType ReKi AccelOnBlade {:}{:} - - "Wind acceleration at nodes on each blade (note if we change the requirement that NumNodes is the same for each blade, this will need to change)" m/s
# Define inputs that are contained on a mesh here:
typedef ^ RotInputType MeshType NacelleMotion - - - "motion on the nacelle" -
typedef ^ RotInputType MeshType TowerMotion - - - "motion on the tower" -
Expand All @@ -426,18 +439,10 @@ typedef ^ RotInputType MeshType BladeRootMotion {:} - - "motion on each blade ro
typedef ^ RotInputType MeshType BladeMotion {:} - - "motion on each blade" -
typedef ^ RotInputType MeshType TFinMotion - - - "motion of tail fin (at tail fin ref point)" -
# Define inputs that are not on a mesh here:
typedef ^ RotInputType BldInputType Bld {:} - - "Blade Inputs" -
typedef ^ RotInputType ReKi InflowOnTower {:}{:} - - "U,V,W at nodes on the tower" m/s
typedef ^ RotInputType ReKi AccelOnTower {:}{:} - - "Wind acceleration at nodes on the tower" m/s
typedef ^ RotInputType ReKi InflowOnHub {3}{1} - - "U,V,W at hub" m/s
typedef ^ RotInputType ReKi InflowOnNacelle {3}{1} - - "U,V,W at nacelle" m/s
typedef ^ RotInputType ReKi InflowOnTailFin {3}{1} - - "U,V,W at tailfin" m/s
typedef ^ RotInputType ReKi AvgDiskVel {3} - 0.0 "disk-averaged U,V,W" m/s
typedef ^ RotInputType ReKi UserProp {:}{:} - - "Optional user property for interpolating airfoils (per element per blade)" -


typedef ^ InputType RotInputType rotors {:} - - "Inputs for each rotor" -
typedef ^ InputType ReKi InflowWakeVel {:}{:} - - "U,V,W at wake points" m/s


# ..... Outputs ...................................................................................................................
Expand Down
Loading

0 comments on commit ce100ad

Please sign in to comment.