Skip to content

Commit

Permalink
Moved rod linear damping to seperate force to address comment in Open…
Browse files Browse the repository at this point in the history
  • Loading branch information
RyanDavies19 committed Jan 7, 2025
1 parent 45356e6 commit f13b845
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 6 deletions.
1 change: 1 addition & 0 deletions modules/moordyn/src/MoorDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -193,6 +193,7 @@ typedef ^ ^ DbKi Dq {:}{:}
typedef ^ ^ DbKi Ap {:}{:} - - "node added mass forcing (transverse)" "[N]"
typedef ^ ^ DbKi Aq {:}{:} - - "node added mass forcing (axial)" "[N]"
typedef ^ ^ DbKi B {:}{:} - - "node bottom contact force" "[N]"
typedef ^ ^ DbKi Bp {:}{:} - - "transverse damping force" "[N]"
typedef ^ ^ DbKi Fnet {:}{:} - - "total force on node" "[N]"
typedef ^ ^ DbKi M {:}{:}{:} - - "node mass matrix" "[kg]"
typedef ^ ^ DbKi FextA {3} - - "external forces from attached lines on/about end A " -
Expand Down
10 changes: 6 additions & 4 deletions modules/moordyn/src/MoorDyn_Rod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ SUBROUTINE Rod_Setup(Rod, RodProp, endCoords, p, ErrStat, ErrMsg)

! allocate node force vectors
ALLOCATE(Rod%W(3, 0:N), Rod%Bo(3, 0:N), Rod%Dp(3, 0:N), Rod%Dq(3, 0:N), Rod%Ap(3, 0:N), &
Rod%Aq(3, 0:N), Rod%Pd(3, 0:N), Rod%B(3, 0:N), Rod%Fnet(3, 0:N), STAT=ErrStat2)
Rod%Aq(3, 0:N), Rod%Pd(3, 0:N), Rod%B(3, 0:N), Rod%Bp(3, 0:N), Rod%Fnet(3, 0:N), STAT=ErrStat2)
if(AllocateFailed("Rod: force arrays")) return

! allocate mass and inverse mass matrices for each node (including ends)
Expand Down Expand Up @@ -763,10 +763,11 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
MagVq = sqrt(SumSqVq)

! transverse and tangenential drag
Rod%Dp(:,I) = VOF * 0.5*p%rhoW*Rod%Cdn* Rod%d* dL * MagVp * Vp - Rod%Blin * Vp_lin * dL ! linear damping added
Rod%Dp(:,I) = VOF * 0.5*p%rhoW*Rod%Cdn* Rod%d* dL * MagVp * Vp
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?


! Transverse damping force
Rod%Bp(:,I) = -Rod%Blin * Vp_lin * dL ! linear damping added. Quadratic damping tbd

! fluid acceleration components for current node
aq = DOT_PRODUCT(Rod%Ud(:,I), Rod%q) * Rod%q ! tangential component of fluid acceleration
Expand Down Expand Up @@ -803,6 +804,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
Rod%Aq = 0.0_DbKi
Rod%Pd = 0.0_DbKi
Rod%B = 0.0_DbKi
Rod%Bp = 0.0_DbKi

END IF

Expand Down Expand Up @@ -873,7 +875,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p)
! ---------------------------- total forces for this node -----------------------------

Rod%Fnet(:,I) = Rod%W(:,I) + Rod%Bo(:,I) + Rod%Dp(:,I) + Rod%Dq(:,I) &
+ Rod%Ap(:,I) + Rod%Aq(:,I) + Rod%Pd(:,I) + Rod%B(:,I)
+ Rod%Ap(:,I) + Rod%Aq(:,I) + Rod%Pd(:,I) + Rod%B(:,I) + Rod%Bp(:,I)


END DO ! I - done looping through nodes
Expand Down
22 changes: 20 additions & 2 deletions modules/moordyn/src/MoorDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,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) :: Blin = 0.0_R8Ki !< Linear damping, transverse damping for body element [[N/(m/s)/m]]
LOGICAL :: isBlin = .false. !< Linear damping, transverse damping for body element is used [-]
REAL(DbKi) :: Blin = 0.0_R8Ki !< Linear damping, transverse damping for rod element [[N/(m/s)/m]]
LOGICAL :: isBlin = .false. !< Linear damping, transverse damping for rod element is used [-]
END TYPE MD_RodProp
! =======================
! ========= MD_Body =======
Expand Down Expand Up @@ -214,6 +214,7 @@ MODULE MoorDyn_Types
REAL(DbKi) , DIMENSION(:,:), ALLOCATABLE :: Ap !< node added mass forcing (transverse) [[N]]
REAL(DbKi) , DIMENSION(:,:), ALLOCATABLE :: Aq !< node added mass forcing (axial) [[N]]
REAL(DbKi) , DIMENSION(:,:), ALLOCATABLE :: B !< node bottom contact force [[N]]
REAL(DbKi) , DIMENSION(:,:), ALLOCATABLE :: Bp !< transverse damping force [[N]]
REAL(DbKi) , DIMENSION(:,:), ALLOCATABLE :: Fnet !< total force on node [[N]]
REAL(DbKi) , DIMENSION(:,:,:), ALLOCATABLE :: M !< node mass matrix [[kg]]
REAL(DbKi) , DIMENSION(1:3) :: FextA = 0.0_R8Ki !< external forces from attached lines on/about end A [-]
Expand Down Expand Up @@ -1350,6 +1351,18 @@ subroutine MD_CopyRod(SrcRodData, DstRodData, CtrlCode, ErrStat, ErrMsg)
end if
DstRodData%B = SrcRodData%B
end if
if (allocated(SrcRodData%Bp)) then
LB(1:2) = lbound(SrcRodData%Bp)
UB(1:2) = ubound(SrcRodData%Bp)
if (.not. allocated(DstRodData%Bp)) then
allocate(DstRodData%Bp(LB(1):UB(1),LB(2):UB(2)), stat=ErrStat2)
if (ErrStat2 /= 0) then
call SetErrStat(ErrID_Fatal, 'Error allocating DstRodData%Bp.', ErrStat, ErrMsg, RoutineName)
return
end if
end if
DstRodData%Bp = SrcRodData%Bp
end if
if (allocated(SrcRodData%Fnet)) then
LB(1:2) = lbound(SrcRodData%Fnet)
UB(1:2) = ubound(SrcRodData%Fnet)
Expand Down Expand Up @@ -1454,6 +1467,9 @@ subroutine MD_DestroyRod(RodData, ErrStat, ErrMsg)
if (allocated(RodData%B)) then
deallocate(RodData%B)
end if
if (allocated(RodData%Bp)) then
deallocate(RodData%Bp)
end if
if (allocated(RodData%Fnet)) then
deallocate(RodData%Fnet)
end if
Expand Down Expand Up @@ -1517,6 +1533,7 @@ subroutine MD_PackRod(RF, Indata)
call RegPackAlloc(RF, InData%Ap)
call RegPackAlloc(RF, InData%Aq)
call RegPackAlloc(RF, InData%B)
call RegPackAlloc(RF, InData%Bp)
call RegPackAlloc(RF, InData%Fnet)
call RegPackAlloc(RF, InData%M)
call RegPack(RF, InData%FextA)
Expand Down Expand Up @@ -1589,6 +1606,7 @@ subroutine MD_UnPackRod(RF, OutData)
call RegUnpackAlloc(RF, OutData%Ap); if (RegCheckErr(RF, RoutineName)) return
call RegUnpackAlloc(RF, OutData%Aq); if (RegCheckErr(RF, RoutineName)) return
call RegUnpackAlloc(RF, OutData%B); if (RegCheckErr(RF, RoutineName)) return
call RegUnpackAlloc(RF, OutData%Bp); if (RegCheckErr(RF, RoutineName)) return
call RegUnpackAlloc(RF, OutData%Fnet); if (RegCheckErr(RF, RoutineName)) return
call RegUnpackAlloc(RF, OutData%M); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%FextA); if (RegCheckErr(RF, RoutineName)) return
Expand Down

0 comments on commit f13b845

Please sign in to comment.