Skip to content

Commit

Permalink
Fixes to the catenary solver, including changing the units of line we…
Browse files Browse the repository at this point in the history
…t weight to N/m
  • Loading branch information
RyanDavies19 committed Sep 28, 2023
1 parent bcedcc8 commit afb944a
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 12 deletions.
2 changes: 1 addition & 1 deletion modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1969,7 +1969,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
! m%LineList(l)%rd(:,0) = (/ 0.0, 0.0, 0.0 /) ! set fairlead end velocities to zero

! set initial line internal node positions using quasi-static model or straight-line interpolation from anchor to fairlead
CALL Line_Initialize( m%LineList(l), m%LineTypeList(m%LineList(l)%PropsIdNum), p%rhoW , ErrStat2, ErrMsg2)
CALL Line_Initialize( m%LineList(l), m%LineTypeList(m%LineList(l)%PropsIdNum), p, ErrStat2, ErrMsg2)
CALL CheckError( ErrStat2, ErrMsg2 )
IF (ErrStat >= AbortErrLev) RETURN

Expand Down
22 changes: 11 additions & 11 deletions modules/moordyn/src/MoorDyn_Line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -242,14 +242,14 @@ END SUBROUTINE SetupLine


!----------------------------------------------------------------------------------------=======
SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
SUBROUTINE Line_Initialize (Line, LineProp, p, ErrStat, ErrMsg)
! calculate initial profile of the line using quasi-static model

TYPE(MD_Line), INTENT(INOUT) :: Line ! the single line object of interest
TYPE(MD_LineProp), INTENT(INOUT) :: LineProp ! the single line property set for the line of interest
REAL(DbKi), INTENT(IN) :: rhoW
INTEGER, INTENT( INOUT ) :: ErrStat ! returns a non-zero value when an error occurs
CHARACTER(*), INTENT( INOUT ) :: ErrMsg ! Error message if ErrStat /= ErrID_None
TYPE(MD_Line), INTENT(INOUT) :: Line ! the single line object of interest
TYPE(MD_LineProp), INTENT(INOUT) :: LineProp ! the single line property set for the line of interest
TYPE(MD_ParameterType), INTENT(IN ) :: p ! Parameters
INTEGER, INTENT( INOUT ) :: ErrStat ! returns a non-zero value when an error occurs
CHARACTER(*), INTENT( INOUT ) :: ErrMsg ! Error message if ErrStat /= ErrID_None

REAL(DbKi) :: COSPhi ! Cosine of the angle between the xi-axis of the inertia frame and the X-axis of the local coordinate system of the current mooring line (-)
REAL(DbKi) :: SINPhi ! Sine of the angle between the xi-axis of the inertia frame and the X-axis of the local coordinate system of the current mooring line (-)
Expand All @@ -263,7 +263,7 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
CHARACTER(ErrMsgLen) :: ErrMsg2 ! Error message if ErrStat2 /= ErrID_None
REAL(DbKi) :: WetWeight
REAL(DbKi) :: SeabedCD = 0.0_DbKi
REAL(DbKi) :: Tol = 0.0001_DbKi
REAL(DbKi) :: Tol = 0.00001_DbKi
REAL(DbKi), ALLOCATABLE :: LSNodes(:)
REAL(DbKi), ALLOCATABLE :: LNodesX(:)
REAL(DbKi), ALLOCATABLE :: LNodesZ(:)
Expand Down Expand Up @@ -292,7 +292,7 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
SINPhi = ( Line%r(2,N) - Line%r(2,0) )/XF
ENDIF

WetWeight = LineProp%w - 0.25*Pi*LineProp%d*LineProp%d*rhoW
WetWeight = (LineProp%w - 0.25*Pi*LineProp%d*LineProp%d*p%rhoW)*p%g

!LineNodes = Line%N + 1 ! number of nodes in line for catenary model to worry about

Expand Down Expand Up @@ -624,7 +624,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, &

HF = MAX( HF, Tol )
XF = MAX( XF, Tol )
ZF = MAX( ZF, TOl )
ZF = MAX( ZF, Tol )



Expand Down Expand Up @@ -730,7 +730,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, &
DET = dXFdHF*dZFdVF - dXFdVF*dZFdHF

IF ( EqualRealNos( DET, 0.0_DbKi ) ) THEN
!bjj: there is a serious problem with the debugger here when DET = 0
!bjj: there is a serious problem with the debugger here when DET = 0
ErrStat = ErrID_Warn
ErrMsg = ' Iteration not convergent (DET is 0) in routine Catenary().'
RETURN
Expand Down Expand Up @@ -961,7 +961,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, &
ZF = -ZF ! Return to orginal value
ENDIF

IF (abs(Z(N+1) - ZF) > Tol) THEN
IF (abs(Z(N) - ZF) > Tol) THEN
! Check fairlead node z position is same as z distance between fairlead and anchor
ErrStat2 = ErrID_Warn
ErrMsg2 = ' Wrong catenary initial profile. Fairlead and anchor vertical seperation has changed in routine Catenary().'
Expand Down

0 comments on commit afb944a

Please sign in to comment.