Skip to content

Commit

Permalink
Merge pull request OpenFAST#2342 from RBergua/dev
Browse files Browse the repository at this point in the history
Linear damping for rod elements in MoorDyn
  • Loading branch information
andrew-platt authored Jul 23, 2024
2 parents 6b4a4aa + 565a8d3 commit 4b8eba6
Show file tree
Hide file tree
Showing 4 changed files with 56 additions and 9 deletions.
20 changes: 17 additions & 3 deletions modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -128,6 +128,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
CHARACTER(40) :: TempStrings(6) ! Array of 6 strings used when parsing comma-separated items
! CHARACTER(1024) :: FileName !


REAL(DbKi) :: depth ! local water depth interpolated from bathymetry grid [m]
Real(DbKi) :: nvec(3) ! local seabed surface normal vector (positive out)

Expand Down Expand Up @@ -724,13 +725,26 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
RETURN
END IF

! parse out entries: Name Diam MassDen Cd Ca CdEnd CaEnd
! parse out entries: Name Diam MassDen Cd Ca CdEnd CaEnd LinDamp
IF (ErrStat2 == 0) THEN
READ(Line,*,IOSTAT=ErrStat2) m%RodTypeList(l)%name, m%RodTypeList(l)%d, m%RodTypeList(l)%w, &
m%RodTypeList(l)%Cdn, m%RodTypeList(l)%Can, m%RodTypeList(l)%CdEnd, m%RodTypeList(l)%CaEnd

m%RodTypeList(l)%Cdn, m%RodTypeList(l)%Can, m%RodTypeList(l)%CdEnd, m%RodTypeList(l)%CaEnd,&
m%RodTypeList(l)%LinDamp ! Linear damping coefficient

if (ErrStat2 == 0) then
m%RodTypeList(l)%isLinDamp = .TRUE. ! linear damping was read
else ! Linear damping not present, so reread the line without it
READ(Line,*,IOSTAT=ErrStat2) m%RodTypeList(l)%name, m%RodTypeList(l)%d, m%RodTypeList(l)%w, &
m%RodTypeList(l)%Cdn, m%RodTypeList(l)%Can, m%RodTypeList(l)%CdEnd, m%RodTypeList(l)%CaEnd

m%RodTypeList(l)%LinDamp = 0.0
m%RodTypeList(l)%isLinDamp = .FALSE.
end if


m%RodTypeList(l)%Cdt = 0.0_DbKi ! not used
m%RodTypeList(l)%Cat = 0.0_DbKi ! not used

END IF

! specify IdNum of rod type for error checking
Expand Down
8 changes: 6 additions & 2 deletions modules/moordyn/src/MoorDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ typedef ^ ^ DbKi stiffXs {30}
typedef ^ ^ DbKi stiffYs {30} - - "y array for stress-strain lookup table"
typedef ^ ^ IntKi nBApoints - 0 - "number of values in stress-strainrate lookup table (0 means using constant c)"
typedef ^ ^ DbKi dampXs {30} - - "x array for stress-strainrate lookup table (up to nCoef)"
typedef ^ ^ DbKi dampYs {30} - - "y array for stress-strainrate lookup table "
typedef ^ ^ DbKi dampYs {30} - - "y array for stress-strainrate lookup table"
typedef ^ ^ IntKi nEIpoints - 0 - "number of values in bending stress-strain lookup table (0 means using constant E)"
typedef ^ ^ DbKi bstiffXs {30} - - "x array for stress-strain lookup table (up to nCoef)"
typedef ^ ^ DbKi bstiffYs {30} - - "y array for stress-strain lookup table"
Expand All @@ -84,6 +84,8 @@ typedef ^ ^ DbKi Cdn -
typedef ^ ^ DbKi Cdt - - - "tangential drag coefficient"
typedef ^ ^ DbKi CdEnd - - - "drag coefficient for rod end" "[-]"
typedef ^ ^ DbKi CaEnd - - - "added mass coefficient for rod end" "[-]"
typedef ^ ^ DbKi LinDamp - - - "Linear damping, transverse damping for body element" "[N/(m/s)/m]"
typedef ^ ^ LOGICAL isLinDamp - - - "Linear damping, transverse damping for body element is used" "-"

# this is the Body type, which holds data for each body object
typedef ^ MD_Body IntKi IdNum - - - "integer identifier of this Point"
Expand Down Expand Up @@ -163,6 +165,8 @@ typedef ^ ^ DbKi Cdn -
typedef ^ ^ DbKi Cdt - - - "" "[-]"
typedef ^ ^ DbKi CdEnd - - - "drag coefficient for rod end" "[-]"
typedef ^ ^ DbKi CaEnd - - - "added mass coefficient for rod end" "[-]"
typedef ^ ^ DbKi LinDamp - - - "Linear damping, transverse damping for rod element" "[N/(m/s)/m]"
typedef ^ ^ LOGICAL isLinDamp - - - "Linear damping, transverse damping for rod element is used" "-"
typedef ^ ^ DbKi time - - - "current time" "[s]"
typedef ^ ^ DbKi roll - - - "roll relative to vertical" "[rad]"
typedef ^ ^ DbKi pitch - - - "pitch relative to vertical" "[rad]"
Expand Down Expand Up @@ -228,7 +232,7 @@ typedef ^ ^ DbKi stiffXs {30}
typedef ^ ^ DbKi stiffYs {30} - - "y array for stress-strain lookup table"
typedef ^ ^ IntKi nBApoints - 0 - "number of values in stress-strainrate lookup table (0 means using constant c)"
typedef ^ ^ DbKi dampXs {30} - - "x array for stress-strainrate lookup table (up to nCoef)"
typedef ^ ^ DbKi dampYs {30} - - "y array for stress-strainrate lookup table "
typedef ^ ^ DbKi dampYs {30} - - "y array for stress-strainrate lookup table"
typedef ^ ^ IntKi nEIpoints - 0 - "number of values in bending stress-strain lookup table (0 means using constant E)"
typedef ^ ^ DbKi bstiffXs {30} - - "x array for stress-strain lookup table (up to nCoef)"
typedef ^ ^ DbKi bstiffYs {30} - - "y array for stress-strain lookup table"
Expand Down
17 changes: 15 additions & 2 deletions modules/moordyn/src/MoorDyn_Rod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,8 @@ SUBROUTINE Rod_Setup(Rod, RodProp, endCoords, p, ErrStat, ErrMsg)
Rod%Cdt = RodProp%Cdt
Rod%CaEnd = RodProp%CaEnd
Rod%CdEnd = RodProp%CdEnd

Rod%linDamp = RodProp%linDamp
Rod%islinDamp = RodProp%islinDamp

! allocate node positions and velocities (NOTE: these arrays start at ZERO)
ALLOCATE(Rod%r(3, 0:N), Rod%rd(3, 0:N), STAT=ErrStat2); if(AllocateFailed("")) return
Expand Down Expand Up @@ -568,6 +569,10 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
Real(DbKi) :: Mnet_i(3) ! moment from an attached line
Real(DbKi) :: Mass_i(3,3) ! mass from an attached line

! Linear damping, Front Energies, July 2024
Real(DbKi) :: Vi_lin(3) ! velocity induced by Rod Motion
Real(DbKi) :: Vp_lin(3), Vq_lin(3) ! transverse and axial components of Rod motion at a given node

! used in lumped 6DOF calculations:
Real(DbKi) :: rRel( 3) ! relative position of each node i from rRef
!Real(DbKi) :: OrMat(3,3) ! rotation matrix to rotate global z to rod's axis
Expand Down Expand Up @@ -738,6 +743,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
!relative flow velocities
DO J = 1, 3
Vi(J) = Rod%U(J,I) - Rod%rd(J,I) ! relative flow velocity over node -- this is where wave velicites would be added
Vi_lin(J) = Rod%rd(J,I) ! linear damping
END DO

! decomponse relative flow into components
Expand All @@ -748,14 +754,21 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
Vp(J) = Vi(J) - Vq(J) ! transverse relative flow component
SumSqVq = SumSqVq + Vq(J)*Vq(J)
SumSqVp = SumSqVp + Vp(J)*Vp(J)

! linear damping
Vq_lin(J) = DOT_PRODUCT( Vi_lin , Rod%q ) * Rod%q(J) ! tangential relative Rod velocity component
Vp_lin(J) = Vi_lin(J) - Vq_lin(J) ! transverse relative Rod velocity component

END DO
MagVp = sqrt(SumSqVp) ! get magnitudes of flow components
MagVq = sqrt(SumSqVq)

! transverse and tangenential drag
Rod%Dp(:,I) = VOF * 0.5*p%rhoW*Rod%Cdn* Rod%d* dL * MagVp * Vp
Rod%Dp(:,I) = VOF * 0.5*p%rhoW*Rod%Cdn* Rod%d* dL * MagVp * Vp - Rod%linDamp * Vp_lin * dL ! linear damping added
Rod%Dq(:,I) = 0.0_DbKi ! 0.25*p%rhoW*Rod%Cdt* Pi*Rod%d* dL * MagVq * Vq <<< should these axial side loads be included?



! fluid acceleration components for current node
aq = DOT_PRODUCT(Rod%Ud(:,I), Rod%q) * Rod%q ! tangential component of fluid acceleration
ap = Rod%Ud(:,I) - aq ! normal component of fluid acceleration
Expand Down
20 changes: 18 additions & 2 deletions modules/moordyn/src/MoorDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ MODULE MoorDyn_Types
REAL(DbKi) , DIMENSION(1:30) :: stiffYs = 0.0_R8Ki !< y array for stress-strain lookup table [-]
INTEGER(IntKi) :: nBApoints = 0 !< number of values in stress-strainrate lookup table (0 means using constant c) [-]
REAL(DbKi) , DIMENSION(1:30) :: dampXs = 0.0_R8Ki !< x array for stress-strainrate lookup table (up to nCoef) [-]
REAL(DbKi) , DIMENSION(1:30) :: dampYs = 0.0_R8Ki !< y array for stress-strainrate lookup table [-]
REAL(DbKi) , DIMENSION(1:30) :: dampYs = 0.0_R8Ki !< y array for stress-strainrate lookup table [-]
INTEGER(IntKi) :: nEIpoints = 0 !< number of values in bending stress-strain lookup table (0 means using constant E) [-]
REAL(DbKi) , DIMENSION(1:30) :: bstiffXs = 0.0_R8Ki !< x array for stress-strain lookup table (up to nCoef) [-]
REAL(DbKi) , DIMENSION(1:30) :: bstiffYs = 0.0_R8Ki !< y array for stress-strain lookup table [-]
Expand All @@ -99,6 +99,8 @@ MODULE MoorDyn_Types
REAL(DbKi) :: Cdt = 0.0_R8Ki !< tangential drag coefficient [-]
REAL(DbKi) :: CdEnd = 0.0_R8Ki !< drag coefficient for rod end [[-]]
REAL(DbKi) :: CaEnd = 0.0_R8Ki !< added mass coefficient for rod end [[-]]
REAL(DbKi) :: LinDamp = 0.0_R8Ki !< Linear damping, transverse damping for body element [[N/(m/s)/m]]
LOGICAL :: isLinDamp = .false. !< Linear damping, transverse damping for body element is used [-]
END TYPE MD_RodProp
! =======================
! ========= MD_Body =======
Expand Down Expand Up @@ -184,6 +186,8 @@ MODULE MoorDyn_Types
REAL(DbKi) :: Cdt = 0.0_R8Ki !< [[-]]
REAL(DbKi) :: CdEnd = 0.0_R8Ki !< drag coefficient for rod end [[-]]
REAL(DbKi) :: CaEnd = 0.0_R8Ki !< added mass coefficient for rod end [[-]]
REAL(DbKi) :: LinDamp = 0.0_R8Ki !< Linear damping, transverse damping for rod element [[N/(m/s)/m]]
LOGICAL :: isLinDamp = .false. !< Linear damping, transverse damping for rod element is used [-]
REAL(DbKi) :: time = 0.0_R8Ki !< current time [[s]]
REAL(DbKi) :: roll = 0.0_R8Ki !< roll relative to vertical [[rad]]
REAL(DbKi) :: pitch = 0.0_R8Ki !< pitch relative to vertical [[rad]]
Expand Down Expand Up @@ -249,7 +253,7 @@ MODULE MoorDyn_Types
REAL(DbKi) , DIMENSION(1:30) :: stiffYs = 0.0_R8Ki !< y array for stress-strain lookup table [-]
INTEGER(IntKi) :: nBApoints = 0 !< number of values in stress-strainrate lookup table (0 means using constant c) [-]
REAL(DbKi) , DIMENSION(1:30) :: dampXs = 0.0_R8Ki !< x array for stress-strainrate lookup table (up to nCoef) [-]
REAL(DbKi) , DIMENSION(1:30) :: dampYs = 0.0_R8Ki !< y array for stress-strainrate lookup table [-]
REAL(DbKi) , DIMENSION(1:30) :: dampYs = 0.0_R8Ki !< y array for stress-strainrate lookup table [-]
INTEGER(IntKi) :: nEIpoints = 0 !< number of values in bending stress-strain lookup table (0 means using constant E) [-]
REAL(DbKi) , DIMENSION(1:30) :: bstiffXs = 0.0_R8Ki !< x array for stress-strain lookup table (up to nCoef) [-]
REAL(DbKi) , DIMENSION(1:30) :: bstiffYs = 0.0_R8Ki !< y array for stress-strain lookup table [-]
Expand Down Expand Up @@ -790,6 +794,8 @@ subroutine MD_CopyRodProp(SrcRodPropData, DstRodPropData, CtrlCode, ErrStat, Err
DstRodPropData%Cdt = SrcRodPropData%Cdt
DstRodPropData%CdEnd = SrcRodPropData%CdEnd
DstRodPropData%CaEnd = SrcRodPropData%CaEnd
DstRodPropData%LinDamp = SrcRodPropData%LinDamp
DstRodPropData%isLinDamp = SrcRodPropData%isLinDamp
end subroutine

subroutine MD_DestroyRodProp(RodPropData, ErrStat, ErrMsg)
Expand All @@ -816,6 +822,8 @@ subroutine MD_PackRodProp(RF, Indata)
call RegPack(RF, InData%Cdt)
call RegPack(RF, InData%CdEnd)
call RegPack(RF, InData%CaEnd)
call RegPack(RF, InData%LinDamp)
call RegPack(RF, InData%isLinDamp)
if (RegCheckErr(RF, RoutineName)) return
end subroutine

Expand All @@ -834,6 +842,8 @@ subroutine MD_UnPackRodProp(RF, OutData)
call RegUnpack(RF, OutData%Cdt); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%CdEnd); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%CaEnd); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%LinDamp); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%isLinDamp); if (RegCheckErr(RF, RoutineName)) return
end subroutine

subroutine MD_CopyBody(SrcBodyData, DstBodyData, CtrlCode, ErrStat, ErrMsg)
Expand Down Expand Up @@ -1107,6 +1117,8 @@ subroutine MD_CopyRod(SrcRodData, DstRodData, CtrlCode, ErrStat, ErrMsg)
DstRodData%Cdt = SrcRodData%Cdt
DstRodData%CdEnd = SrcRodData%CdEnd
DstRodData%CaEnd = SrcRodData%CaEnd
DstRodData%LinDamp = SrcRodData%LinDamp
DstRodData%isLinDamp = SrcRodData%isLinDamp
DstRodData%time = SrcRodData%time
DstRodData%roll = SrcRodData%roll
DstRodData%pitch = SrcRodData%pitch
Expand Down Expand Up @@ -1447,6 +1459,8 @@ subroutine MD_PackRod(RF, Indata)
call RegPack(RF, InData%Cdt)
call RegPack(RF, InData%CdEnd)
call RegPack(RF, InData%CaEnd)
call RegPack(RF, InData%LinDamp)
call RegPack(RF, InData%isLinDamp)
call RegPack(RF, InData%time)
call RegPack(RF, InData%roll)
call RegPack(RF, InData%pitch)
Expand Down Expand Up @@ -1516,6 +1530,8 @@ subroutine MD_UnPackRod(RF, OutData)
call RegUnpack(RF, OutData%Cdt); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%CdEnd); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%CaEnd); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%LinDamp); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%isLinDamp); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%time); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%roll); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%pitch); if (RegCheckErr(RF, RoutineName)) return
Expand Down

0 comments on commit 4b8eba6

Please sign in to comment.