Skip to content

Commit

Permalink
Cleaner line error printing
Browse files Browse the repository at this point in the history
  • Loading branch information
RyanDavies19 committed Sep 13, 2023
1 parent 8b8cb60 commit 357d827
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 16 deletions.
28 changes: 18 additions & 10 deletions modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
REAL(ReKi) :: OrMat(3,3) ! rotation matrix for setting fairlead positions correctly if there is initial platform rotation
REAL(ReKi) :: OrMat2(3,3)
REAL(R8Ki) :: OrMatRef(3,3)
REAL(DbKi), ALLOCATABLE :: FairTensIC(:,:)! array of size nCpldPoints, 3 to store three latest fairlead tensions of each line
REAL(DbKi), ALLOCATABLE :: FairTensIC(:,:)! array of size nCpldPoints, 10 latest fairlead tensions of each line
CHARACTER(20) :: TempString ! temporary string for incidental use
INTEGER(IntKi) :: ErrStat2 ! Error status of the operation
CHARACTER(ErrMsgLen) :: ErrMsg2 ! Error message if ErrStat2 /= ErrID_None
Expand Down Expand Up @@ -1718,12 +1718,14 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er

ALLOCATE ( u%CoupledKinematics(p%nTurbines), STAT = ErrStat2 )
IF ( ErrStat2 /= ErrID_None ) THEN
CALL CheckError(ErrID_Fatal, ' Error allocating CoupledKinematics input array.')
ErrMsg2 = ' Error allocating CoupledKinematics input array.'
CALL CheckError(ErrID_Fatal, ErrMsg2)
RETURN
END IF
ALLOCATE ( y%CoupledLoads(p%nTurbines), STAT = ErrStat2 )
IF ( ErrStat2 /= ErrID_None ) THEN
CALL CheckError(ErrID_Fatal, ' Error allocating CoupledLoads output array.')
ErrMsg2 = ' Error allocating CoupledLoads output array.'
CALL CheckError(ErrID_Fatal, ErrMsg2)
RETURN
END IF

Expand Down Expand Up @@ -1970,7 +1972,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
CALL Line_Initialize( m%LineList(l), m%LineTypeList(m%LineList(l)%PropsIdNum), p%rhoW , ErrStat2, ErrMsg2)
CALL CheckError( ErrStat2, ErrMsg2 )
IF (ErrStat >= AbortErrLev) RETURN
!IF (ErrStat >= ErrId_Warn) CALL WrScr(" Note: Catenary pre-solver was unsuccessful for one or more lines so started with linear node spacing instead.") ! make this statement more accurate
IF (ErrStat >= ErrId_Warn) CALL WrScr(' Catenary solve of Line '//trim(Num2LStr(m%LineList(l)%IdNum))//' unsuccessful. Initializing as linear.')

IF (wordy > 2) print *, "Line ", l, " with NumSegs =", N
IF (wordy > 2) print *, "its states range from index ", m%LineStateIs1(l), " to ", m%LineStateIsN(l)
Expand Down Expand Up @@ -2140,11 +2142,11 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
END DO


! provide status message
! bjj: putting this in a string so we get blanks to cover up previous values (if current string is shorter than previous one)
Message = ' t='//trim(Num2LStr(t))//' FairTen 1: '//trim(Num2LStr(FairTensIC(1,1)))// &
', '//trim(Num2LStr(FairTensIC(1,2)))//', '//trim(Num2LStr(FairTensIC(1,3)))
CALL WrOver( Message )
! ! provide status message
! ! bjj: putting this in a string so we get blanks to cover up previous values (if current string is shorter than previous one)
! Message = ' t='//trim(Num2LStr(t))//' FairTen 1: '//trim(Num2LStr(FairTensIC(1,1)))// &
! ', '//trim(Num2LStr(FairTensIC(1,2)))//', '//trim(Num2LStr(FairTensIC(1,3)))
! CALL WrOver( Message )

! check for convergence (compare current tension at each fairlead with previous 9 values)
IF (I > 9) THEN
Expand All @@ -2166,6 +2168,10 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er

IF (Converged == 1) THEN ! if we made it with all cases satisfying the threshold
CALL WrScr(' Fairlead tensions converged to '//trim(Num2LStr(100.0*InputFileDat%threshIC))//'% after '//trim(Num2LStr(t))//' seconds.')
DO l = 1, p%nLines
CALL WrScr(' Fairlead tension: '//trim(Num2LStr(FairTensIC(l,1))))
CALL WrScr(' Fairlead forces: '//trim(Num2LStr(m%LineList(l)%Fnet(1, m%LineList(l)%N)))//', '//trim(Num2LStr(m%LineList(l)%Fnet(2, m%LineList(l)%N)))//', '//trim(Num2LStr(m%LineList(l)%Fnet(3, m%LineList(l)%N))))
ENDDO
EXIT ! break out of the time stepping loop
END IF
END IF
Expand Down Expand Up @@ -2233,7 +2239,7 @@ SUBROUTINE CheckError(ErrID,Msg)

! Passed arguments
INTEGER(IntKi), INTENT(IN) :: ErrID ! The error identifier (ErrStat)
CHARACTER(*), INTENT(IN) :: Msg ! The error message (ErrMsg)
CHARACTER(*), INTENT(INOUT) :: Msg ! The error message (ErrMsg)

INTEGER(IntKi) :: ErrStat3 ! The error identifier (ErrStat)
CHARACTER(1024) :: ErrMsg3 ! The error message (ErrMsg)
Expand All @@ -2246,6 +2252,8 @@ SUBROUTINE CheckError(ErrID,Msg)
ErrMsg = TRIM(ErrMsg)//' MD_Init:'//TRIM(Msg)
ErrStat = MAX(ErrStat, ErrID)

Msg = "" ! Reset the error message now that it has been logged into ErrMsg

! Clean up if we're going to return on error: close files, deallocate local arrays


Expand Down
10 changes: 4 additions & 6 deletions modules/moordyn/src/MoorDyn_Line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -343,7 +343,7 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
Line%r(3,J) = Line%r(3,0) + (Line%r(3,N) - Line%r(3,0))*REAL(J, DbKi)/REAL(N, DbKi)
END DO

CALL WrScr(" Vertical initial profile for Line "//trim(Num2LStr(Line%IdNum))//".")
CALL WrScr(' Vertical initial profile for Line '//trim(Num2LStr(Line%IdNum))//'.')

ELSE ! If the line is not vertical, solve for the catenary profile

Expand All @@ -354,7 +354,7 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
IF ((abs(LNodesZ(N+1) - ZF) > Tol) .AND. (ErrStat2 == ErrID_None)) THEN
! Check fairlead node z position is same as z distance between fairlead and anchor
ErrStat2 = ErrID_Warn
ErrMsg2 = ' Wrong catenary initial profile for Line '//trim(Num2LStr(Line%IdNum))//'. Fairlead and anchor vertical seperation has changed.'
ErrMsg2 = ' Wrong catenary initial profile. Fairlead and anchor vertical seperation has changed. '
ENDIF

IF (ErrStat2 == ErrID_None) THEN ! if it worked, use it
Expand All @@ -369,9 +369,7 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg)
ENDDO ! J - All nodes per line where the line position and tension can be output

ELSE ! if there is a problem with the catenary approach, just stretch the nodes linearly between fairlead and anchor

CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, 'Line_Initialize')
CALL WrScr(" Catenary solve of Line "//trim(Num2LStr(Line%IdNum))//" unsuccessful. Initializing as linear.")
CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, ' Line_Initialize: Line '//trim(Num2LStr(Line%IdNum))//' ')

! print *, "Node positions: "

Expand Down Expand Up @@ -593,7 +591,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, &
ELSEIF ( W == 0.0_DbKi ) THEN ! .TRUE. when the weight of the line in fluid is zero so that catenary solution is ill-conditioned
ErrStat = ErrID_Warn
ErrMsg = ' The weight of the line in fluid must not be zero. '// &
' Routine Catenary() cannot solve quasi-static mooring line solution.'
'Routine Catenary() cannot solve quasi-static mooring line solution.'
RETURN


Expand Down

0 comments on commit 357d827

Please sign in to comment.