From 1d8ecffdb53b1e9acfac207f631a083453fc16c3 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 5 Jul 2023 11:35:46 -0700 Subject: [PATCH 01/13] Standardizing output options w/ MoorDynV2 and finished changing connections to points --- modules/moordyn/src/MoorDyn.f90 | 346 ++++++------- modules/moordyn/src/MoorDyn_Body.f90 | 60 +-- modules/moordyn/src/MoorDyn_Driver.f90 | 6 +- modules/moordyn/src/MoorDyn_IO.f90 | 378 +++++++++----- modules/moordyn/src/MoorDyn_Line.f90 | 30 +- modules/moordyn/src/MoorDyn_Misc.f90 | 6 +- modules/moordyn/src/MoorDyn_Point.f90 | 238 ++++----- modules/moordyn/src/MoorDyn_Registry.txt | 82 +-- modules/moordyn/src/MoorDyn_Rod.f90 | 18 +- modules/moordyn/src/MoorDyn_Types.f90 | 604 +++++++++++------------ 10 files changed, 955 insertions(+), 813 deletions(-) diff --git a/modules/moordyn/src/MoorDyn.f90 b/modules/moordyn/src/MoorDyn.f90 index bbd5fc9328..8d89af50c7 100644 --- a/modules/moordyn/src/MoorDyn.f90 +++ b/modules/moordyn/src/MoorDyn.f90 @@ -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 nCpldCons, 3 to store three latest fairlead tensions of each line + REAL(DbKi), ALLOCATABLE :: FairTensIC(:,:)! array of size nCpldPoints, 3 to store three 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 @@ -214,13 +214,13 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! allocate some parameter arrays that are for each turbine (size 1 if regular OpenFAST use) allocate( p%nCpldBodies( p%nTurbines)) allocate( p%nCpldRods ( p%nTurbines)) - allocate( p%nCpldCons ( p%nTurbines)) + allocate( p%nCpldPoints ( p%nTurbines)) allocate( p%TurbineRefPos(3, p%nTurbines)) ! initialize the arrays (to zero, except for passed in farm turbine reference positions) p%nCpldBodies = 0 p%nCpldRods = 0 - p%nCpldCons = 0 + p%nCpldPoints = 0 if (InitInp%FarmSize > 0) then p%TurbineRefPos = InitInp%TurbineRefPos ! copy over turbine reference positions for later use @@ -346,7 +346,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! find how many elements of this type there are Line = NextLine(i) DO while (INDEX(Line, "---") == 0) ! while we DON'T find another header line - p%nConnects = p%nConnects + 1 + p%nPoints = p%nPoints + 1 Line = NextLine(i) END DO @@ -483,13 +483,13 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er end do - p%nConnectsExtra = p%nConnects + 2*p%nLines ! set maximum number of connections, accounting for possible detachment of each line end and a connection for that + p%nPointsExtra = p%nPoints + 2*p%nLines ! set maximum number of points, accounting for possible detachment of each line end and a point for that IF (wordy > 0) print *, " Identified ", p%nLineTypes , "LineTypes in input file." IF (wordy > 0) print *, " Identified ", p%nRodTypes , "RodTypes in input file." IF (wordy > 0) print *, " Identified ", p%nBodies , "Bodies in input file." IF (wordy > 0) print *, " Identified ", p%nRods , "Rods in input file." - IF (wordy > 0) print *, " Identified ", p%nConnects , "Connections in input file." + IF (wordy > 0) print *, " Identified ", p%nPoints , "Points in input file." IF (wordy > 0) print *, " Identified ", p%nLines , "Lines in input file." IF (wordy > 0) print *, " Identified ", nOpts , "Options in input file." @@ -535,7 +535,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ALLOCATE(m%BodyList( p%nBodies ), STAT = ErrStat2 ); if(AllocateFailed("BodyList" )) return ALLOCATE(m%RodList( p%nRods ), STAT = ErrStat2 ); if(AllocateFailed("RodList" )) return - ALLOCATE(m%ConnectList( p%nConnects ), STAT = ErrStat2 ); if(AllocateFailed("ConnectList" )) return + ALLOCATE(m%PointList( p%nPoints ), STAT = ErrStat2 ); if(AllocateFailed("PointList" )) return ALLOCATE(m%LineList( p%nLines ), STAT = ErrStat2 ); if(AllocateFailed("LineList" )) return ALLOCATE(m%FailList( p%nFails ), STAT = ErrStat2 ); if(AllocateFailed("FailList" )) return @@ -544,16 +544,16 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! Allocate associated index arrays (note: some are allocated larger than will be used, for simplicity) ALLOCATE(m%BodyStateIs1(p%nBodies ), m%BodyStateIsN(p%nBodies ), STAT=ErrStat2); if(AllocateFailed("BodyStateIs1/N")) return ALLOCATE(m%RodStateIs1(p%nRods ), m%RodStateIsN(p%nRods ), STAT=ErrStat2); if(AllocateFailed("RodStateIs1/N" )) return - ALLOCATE(m%ConStateIs1(p%nConnects), m%ConStateIsN(p%nConnects), STAT=ErrStat2); if(AllocateFailed("ConStateIs1/N" )) return + ALLOCATE(m%PointStateIs1(p%nPoints), m%PointStateIsN(p%nPoints), STAT=ErrStat2); if(AllocateFailed("PointStateIs1/N" )) return ALLOCATE(m%LineStateIs1(p%nLines) , m%LineStateIsN(p%nLines) , STAT=ErrStat2); if(AllocateFailed("LineStateIs1/N")) return ALLOCATE(m%FreeBodyIs( p%nBodies ), STAT=ErrStat2); if(AllocateFailed("FreeBodyIs")) return ALLOCATE(m%FreeRodIs( p%nRods ), STAT=ErrStat2); if(AllocateFailed("FreeRodIs")) return - ALLOCATE(m%FreeConIs( p%nConnects), STAT=ErrStat2); if(AllocateFailed("FreeConnectIs")) return + ALLOCATE(m%FreePointIs( p%nPoints), STAT=ErrStat2); if(AllocateFailed("FreePointIs")) return ALLOCATE(m%CpldBodyIs(p%nBodies , p%nTurbines), STAT=ErrStat2); if(AllocateFailed("CpldBodyIs")) return ALLOCATE(m%CpldRodIs( p%nRods , p%nTurbines), STAT=ErrStat2); if(AllocateFailed("CpldRodIs")) return - ALLOCATE(m%CpldConIs(p%nConnects, p%nTurbines), STAT=ErrStat2); if(AllocateFailed("CpldConnectIs")) return + ALLOCATE(m%CpldPointIs(p%nPoints, p%nTurbines), STAT=ErrStat2); if(AllocateFailed("CpldPointIs")) return ! ---------------------- now go through again and process file contents -------------------- @@ -1082,7 +1082,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er Line = NextLine(i) ! process each point - DO l = 1,p%nConnects + DO l = 1,p%nPoints !read into a line Line = NextLine(i) @@ -1096,9 +1096,9 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! parse out entries: PointID Attachment X Y Z M V CdA Ca IF (ErrStat2 == 0) THEN - READ(Line,*,IOSTAT=ErrStat2) m%ConnectList(l)%IdNum, tempString1, tempArray(1), & - tempArray(2), tempString4, m%ConnectList(l)%conM, & - m%ConnectList(l)%conV, m%ConnectList(l)%conCdA, m%ConnectList(l)%conCa + READ(Line,*,IOSTAT=ErrStat2) m%PointList(l)%IdNum, tempString1, tempArray(1), & + tempArray(2), tempString4, m%PointList(l)%pointM, & + m%PointList(l)%pointV, m%PointList(l)%pointCdA, m%PointList(l)%pointCa CALL Conv2UC(tempString4) ! convert to uppercase so that matching is not case-sensitive @@ -1112,9 +1112,9 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er end if ! not used - m%ConnectList(l)%conFX = 0.0_DbKi - m%ConnectList(l)%conFY = 0.0_DbKi - m%ConnectList(l)%conFZ = 0.0_DbKi + m%PointList(l)%pointFX = 0.0_DbKi + m%PointList(l)%pointFY = 0.0_DbKi + m%PointList(l)%pointFZ = 0.0_DbKi END IF @@ -1122,59 +1122,59 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er IF ( ErrStat2 /= 0 ) THEN CALL WrScr(' Unable to parse Point '//trim(Num2LStr(l))//' row in input file.') ! Specific screen output because errors likely CALL WrScr(' Ensure row has all 9 columns, including CdA and Ca.') ! to be caused by non-updated input file formats. - CALL SetErrStat( ErrID_Fatal, 'Failed to read connects.' , ErrStat, ErrMsg, RoutineName ) ! would be nice to specify which line <<<<<<<<< + CALL SetErrStat( ErrID_Fatal, 'Failed to read points.' , ErrStat, ErrMsg, RoutineName ) ! would be nice to specify which line <<<<<<<<< CALL CleanUp() RETURN END IF - m%ConnectList(l)%r = tempArray(1:3) ! set initial, or reference, node position (for coupled or child objects, this will be the local reference location about the parent) + m%PointList(l)%r = tempArray(1:3) ! set initial, or reference, node position (for coupled or child objects, this will be the local reference location about the parent) - !----------- process connection type ----------------- + !----------- process point type ----------------- call DecomposeString(tempString1, let1, num1, let2, num2, let3) if ((let1 == "ANCHOR") .or. (let1 == "FIXED") .or. (let1 == "FIX")) then - m%ConnectList(l)%typeNum = 1 + m%PointList(l)%typeNum = 1 - !m%ConnectList(l)%r = tempArray(1:3) ! set initial node position + !m%PointList(l)%r = tempArray(1:3) ! set initial node position - CALL Body_AddConnect(m%GroundBody, l, tempArray(1:3)) ! add connection l to Ground body + CALL Body_AddPoint(m%GroundBody, l, tempArray(1:3)) ! add point l to Ground body else if (let1 == "BODY") then ! attached to a body if (len_trim(num1) > 0) then READ(num1, *) J ! convert to int, representing parent body index if ((J <= p%nBodies) .and. (J > 0)) then - m%ConnectList(l)%typeNum = 1 + m%PointList(l)%typeNum = 1 - CALL Body_AddConnect(m%BodyList(J), l, tempArray(1:3)) ! add connection l to Ground body + CALL Body_AddPoint(m%BodyList(J), l, tempArray(1:3)) ! add point l to Ground body else - CALL SetErrStat( ErrID_Fatal, "Body ID out of bounds for Connection "//trim(Num2LStr(l))//".", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Body ID out of bounds for Point "//trim(Num2LStr(l))//".", ErrStat, ErrMsg, RoutineName ) return end if else - CALL SetErrStat( ErrID_Fatal, "No number provided for Connection "//trim(Num2LStr(l))//" Body attachment.", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "No number provided for Point "//trim(Num2LStr(l))//" Body attachment.", ErrStat, ErrMsg, RoutineName ) return end if else if ((let1 == "VESSEL") .or. (let1 == "VES") .or. (let1 == "COUPLED") .or. (let1 == "CPLD")) then ! if a fairlead, add to list and add - m%ConnectList(l)%typeNum = -1 - p%nCpldCons(1)=p%nCpldCons(1)+1 - m%CpldConIs(p%nCpldCons(1),1) = l + m%PointList(l)%typeNum = -1 + p%nCpldPoints(1)=p%nCpldPoints(1)+1 + m%CpldPointIs(p%nCpldPoints(1),1) = l - else if ((let1 == "CONNECT") .or. (let1 == "CON") .or. (let1 == "FREE")) then - m%ConnectList(l)%typeNum = 0 + else if ((let1 == "POINT") .or. (let1 == "P") .or. (let1 == "FREE")) then + m%PointList(l)%typeNum = 0 - p%nFreeCons=p%nFreeCons+1 ! add this pinned rod to the free list because it is half free + p%nFreePoints=p%nFreePoints+1 ! add this pinned rod to the free list because it is half free - m%ConStateIs1(p%nFreeCons) = Nx+1 - m%ConStateIsN(p%nFreeCons) = Nx+6 - Nx = Nx + 6 ! add 12 state variables for free Connection + m%PointStateIs1(p%nFreePoints) = Nx+1 + m%PointStateIsN(p%nFreePoints) = Nx+6 + Nx = Nx + 6 ! add 12 state variables for free Point - m%FreeConIs(p%nFreeCons) = l + m%FreePointIs(p%nFreePoints) = l - !m%ConnectList(l)%r = tempArray(1:3) ! set initial node position + !m%PointList(l)%r = tempArray(1:3) ! set initial node position else if ((let1 == "TURBINE") .or. (let1 == "T")) then ! turbine-coupled in FAST.Farm case @@ -1183,50 +1183,50 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er if ((J <= p%nTurbines) .and. (J > 0)) then - m%ConnectList(l)%TypeNum = -1 ! set as coupled type - p%nCpldCons(J) = p%nCpldCons(J) + 1 ! increment counter for the appropriate turbine - m%CpldConIs(p%nCpldCons(J),J) = l - CALL WrScr(' added connection '//TRIM(int2lstr(l))//' as fairlead for turbine '//trim(int2lstr(J))) + m%PointList(l)%TypeNum = -1 ! set as coupled type + p%nCpldPoints(J) = p%nCpldPoints(J) + 1 ! increment counter for the appropriate turbine + m%CpldPointIs(p%nCpldPoints(J),J) = l + CALL WrScr(' added point '//TRIM(int2lstr(l))//' as fairlead for turbine '//trim(int2lstr(J))) else - CALL SetErrStat( ErrID_Fatal, "Turbine ID out of bounds for Connection "//trim(Num2LStr(l))//".", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Turbine ID out of bounds for Point "//trim(Num2LStr(l))//".", ErrStat, ErrMsg, RoutineName ) return end if else - CALL SetErrStat( ErrID_Fatal, "No number provided for Connection "//trim(Num2LStr(l))//" Turbine attachment.", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "No number provided for Point "//trim(Num2LStr(l))//" Turbine attachment.", ErrStat, ErrMsg, RoutineName ) return end if else - CALL SetErrStat( ErrID_Fatal, "Unidentified Type/BodyID for Connection "//trim(Num2LStr(l))//": "//trim(tempString1), ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Unidentified Type/BodyID for Point "//trim(Num2LStr(l))//": "//trim(tempString1), ErrStat, ErrMsg, RoutineName ) return end if ! set initial velocity to zero - m%ConnectList(l)%rd(1) = 0.0_DbKi - m%ConnectList(l)%rd(2) = 0.0_DbKi - m%ConnectList(l)%rd(3) = 0.0_DbKi + m%PointList(l)%rd(1) = 0.0_DbKi + m%PointList(l)%rd(2) = 0.0_DbKi + m%PointList(l)%rd(3) = 0.0_DbKi !also set number of attached lines to zero initially - m%ConnectList(l)%nAttached = 0 + m%PointList(l)%nAttached = 0 ! check for sequential IdNums - IF ( m%ConnectList(l)%IdNum .NE. l ) THEN - CALL SetErrStat( ErrID_Fatal, 'Connection numbers must be sequential starting from 1.', ErrStat, ErrMsg, RoutineName ) + IF ( m%PointList(l)%IdNum .NE. l ) THEN + CALL SetErrStat( ErrID_Fatal, 'Point numbers must be sequential starting from 1.', ErrStat, ErrMsg, RoutineName ) CALL CleanUp() RETURN END IF IF ( ErrStat2 /= 0 ) THEN - CALL SetErrStat( ErrID_Fatal, 'Failed to read data for Connection '//trim(Num2LStr(l)), ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, 'Failed to read data for Point '//trim(Num2LStr(l)), ErrStat, ErrMsg, RoutineName ) CALL CleanUp() RETURN END IF - IF (wordy > 0) print *, "Set up Point ", l, " of type ", m%ConnectList(l)%typeNum + IF (wordy > 0) print *, "Set up Point ", l, " of type ", m%PointList(l)%typeNum END DO ! l = 1,p%nRods @@ -1306,17 +1306,17 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er return end if else - CALL SetErrStat( ErrID_Fatal, "Error: rod connection ID out of bounds for line "//trim(Num2LStr(l))//" end A attachment.", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Error: rod point ID out of bounds for line "//trim(Num2LStr(l))//" end A attachment.", ErrStat, ErrMsg, RoutineName ) return end if - ! if J starts with a "C" or "Con" or goes straight ot the number then it's attached to a Connection - else if ((len_trim(let1)==0) .or. (let1 == "C") .or. (let1 == "CON")) then + ! if J starts with a "P" or "Point" or goes straight ot the number then it's attached to a Point + else if ((len_trim(let1)==0) .or. (let1 == "P") .or. (let1 == "POINT")) then - if ((J <= p%nConnects) .and. (J > 0)) then - CALL Connect_AddLine(m%ConnectList(J), l, 0) ! add line l (end A, denoted by 0) to connection J + if ((J <= p%nPoints) .and. (J > 0)) then + CALL Point_AddLine(m%PointList(J), l, 0) ! add line l (end A, denoted by 0) to point J else - CALL SetErrStat( ErrID_Fatal, "Error: connection out of bounds for line "//trim(Num2LStr(l))//" end A attachment.", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Error: point out of bounds for line "//trim(Num2LStr(l))//" end A attachment.", ErrStat, ErrMsg, RoutineName ) return end if @@ -1351,13 +1351,13 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er return end if - ! if J starts with a "C" or "Con" or goes straight ot the number then it's attached to a Connection - else if ((len_trim(let1)==0) .or. (let1 == "C") .or. (let1 == "CON")) then + ! if J starts with a "P" or "Point" or goes straight ot the number then it's attached to a Point + else if ((len_trim(let1)==0) .or. (let1 == "P") .or. (let1 == "POINT")) then - if ((J <= p%nConnects) .and. (J > 0)) then - CALL Connect_AddLine(m%ConnectList(J), l, 1) ! add line l (end B, denoted by 1) to connection J + if ((J <= p%nPoints) .and. (J > 0)) then + CALL Point_AddLine(m%PointList(J), l, 1) ! add line l (end B, denoted by 1) to point J else - CALL SetErrStat( ErrID_Fatal, "Error: connection out of bounds for line "//trim(Num2LStr(l))//" end B attachment.", ErrStat, ErrMsg, RoutineName ) + CALL SetErrStat( ErrID_Fatal, "Error: point out of bounds for line "//trim(Num2LStr(l))//" end B attachment.", ErrStat, ErrMsg, RoutineName ) return end if @@ -1564,35 +1564,35 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er !------------------------------------------------------------------------------------------------- - ! Connect mooring system together and make necessary allocations + ! Point mooring system together and make necessary allocations !------------------------------------------------------------------------------------------------- CALL WrNr(' Created mooring system: ' ) -! p%NAnchs = 0 ! this is the number of "fixed" type Connections. <<<<<<<<<<<<<< +! p%NAnchs = 0 ! this is the number of "fixed" type Points. <<<<<<<<<<<<<< - CALL WrScr(trim(Num2LStr(p%nLines))//' lines, '//trim(Num2LStr(p%NConnects))//' points, '//trim(Num2LStr(p%nRods))//' rods, '//trim(Num2LStr(p%nBodies))//' bodies.') + CALL WrScr(trim(Num2LStr(p%nLines))//' lines, '//trim(Num2LStr(p%NPoints))//' points, '//trim(Num2LStr(p%nRods))//' rods, '//trim(Num2LStr(p%nBodies))//' bodies.') ! ! now go back through and record the fairlead Id numbers (this >>>WAS<<< all the "connecting" that's required) <<<< ! J = 1 ! counter for fairlead number - ! K = 1 ! counter for connect number - ! DO I = 1,p%NConnects - ! IF (m%ConnectList(I)%typeNum == 1) THEN - ! m%CpldConIs(J) = I ! if a vessel connection, add ID to list + ! K = 1 ! counter for point number + ! DO I = 1,p%NPoints + ! IF (m%PointList(I)%typeNum == 1) THEN + ! m%CpldPointIs(J) = I ! if a vessel point, add ID to list ! J = J + 1 - ! ELSE IF (m%ConnectList(I)%typeNum == 2) THEN - ! m%FreeConIs(K) = I ! if a connect connection, add ID to list + ! ELSE IF (m%PointList(I)%typeNum == 2) THEN + ! m%FreePointIs(K) = I ! if a point, add ID to list ! K = K + 1 ! END IF ! END DO IF (wordy > 1) print *, "nLineTypes = ",p%nLineTypes IF (wordy > 1) print *, "nRodTypes = ",p%nRodTypes - IF (wordy > 1) print *, "nConnects = ",p%nConnects - IF (wordy > 1) print *, "nConnectsExtra = ",p%nConnectsExtra + IF (wordy > 1) print *, "nPoints = ",p%nPoints + IF (wordy > 1) print *, "nPointsExtra = ",p%nPointsExtra IF (wordy > 1) print *, "nBodies = ",p%nBodies IF (wordy > 1) print *, "nRods = ",p%nRods IF (wordy > 1) print *, "nLines = ",p%nLines @@ -1600,15 +1600,15 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er IF (wordy > 1) print *, "nFails = ",p%nFails IF (wordy > 1) print *, "nFreeBodies = ",p%nFreeBodies IF (wordy > 1) print *, "nFreeRods = ",p%nFreeRods - IF (wordy > 1) print *, "nFreeCons = ",p%nFreeCons + IF (wordy > 1) print *, "nFreePoints = ",p%nFreePoints IF (wordy > 1) print *, "nCpldBodies = ",p%nCpldBodies IF (wordy > 1) print *, "nCpldRods = ",p%nCpldRods - IF (wordy > 1) print *, "nCpldCons = ",p%nCpldCons + IF (wordy > 1) print *, "nCpldPoints = ",p%nCpldPoints IF (wordy > 1) print *, "NConns = ",p%NConns IF (wordy > 1) print *, "NAnchs = ",p%NAnchs - IF (wordy > 2) print *, "FreeConIs are ", m%FreeConIs - IF (wordy > 2) print *, "CpldConIs are ", m%CpldConIs + IF (wordy > 2) print *, "FreePointIs are ", m%FreePointIs + IF (wordy > 2) print *, "CpldPointIs are ", m%CpldPointIs ! write system description to log file @@ -1626,10 +1626,10 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er - ! ! allocate list of starting and ending state vector indices for each free connection - ! ALLOCATE ( m%ConStateIs1(p%nFreeCons), m%ConStateIsN(p%nFreeCons), STAT = ErrStat ) + ! ! allocate list of starting and ending state vector indices for each free point + ! ALLOCATE ( m%PointStateIs1(p%nFreePoints), m%PointStateIsN(p%nFreePoints), STAT = ErrStat ) ! IF ( ErrStat /= ErrID_None ) THEN - ! CALL CheckError(ErrID_Fatal, ' Error allocating ConStateIs array.') + ! CALL CheckError(ErrID_Fatal, ' Error allocating PointStateIs array.') ! RETURN ! END IF ! @@ -1648,13 +1648,13 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! ! Free Bodies... ! ! Free Rods... ! - ! ! Free Connections... - ! DO l = 1, p%nFreeCons + ! ! Free Points... + ! DO l = 1, p%nFreePoints ! J = J + 1 ! assign start index - ! m%ConStateIs1(l) = J + ! m%PointStateIs1(l) = J ! ! J = J + 5 ! assign end index (5 entries further, since nodes have 2*3 states) - ! m%ConStateIsN(l) = J + ! m%PointStateIsN(l) = J ! END DO ! ! ! Lines @@ -1703,11 +1703,11 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er ! m%GroundBody%OrMat = EulerConstruct( m%GroundBody%r6(4:6) ) ! make sure it's OrMat is set up <<< need to check this approach ! ! first set/update the kinematics of all the fixed things (>>>> eventually do this by using a ground body <<<<) - ! ! only doing connections so far - ! DO J = 1,p%nConnects - ! if (m%ConnectList(J)%typeNum == 1) then + ! ! only doing points so far + ! DO J = 1,p%nPoints + ! if (m%PointList(J)%typeNum == 1) then ! ! set the attached line endpoint positions: - ! CALL Connect_SetKinematics(m%ConnectList(J), m%ConnectList(J)%r, (/0.0_DbKi,0.0_DbKi,0.0_DbKi/), 0.0_DbKi, m%LineList) + ! CALL Point_SetKinematics(m%PointList(J), m%PointList(J)%r, (/0.0_DbKi,0.0_DbKi,0.0_DbKi/), 0.0_DbKi, m%LineList) ! end if ! END DO @@ -1736,7 +1736,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er IF (ErrStat >= AbortErrLev) RETURN ! count number of coupling nodes needed for the mesh of this turbine - K = p%nCpldBodies(iTurb) + p%nCpldRods(iTurb) + p%nCpldCons(iTurb) + K = p%nCpldBodies(iTurb) + p%nCpldRods(iTurb) + p%nCpldPoints(iTurb) if (K == 0) K = 1 ! Always have at least one node (it will be a dummy node if no fairleads are attached) ! create input mesh for fairlead kinematics @@ -1750,7 +1750,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er CALL CheckError( ErrStat2, ErrMsg2 ) IF (ErrStat >= AbortErrLev) RETURN - ! note: in MoorDyn-F v2, the points in the mesh correspond in order to all the coupled bodies, then rods, then connections + ! note: in MoorDyn-F v2, the points in the mesh correspond in order to all the coupled bodies, then rods, then points ! >>> make sure all coupled objects have been offset correctly by the PtfmInit values, including if it's a farm situation -- below or where the objects are first created <<<< @@ -1809,11 +1809,11 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er CALL Rod_SetKinematics(m%RodList(m%CpldRodIs(l,iTurb)), REAL(rRef,R8Ki), m%zeros6, m%zeros6, 0.0_DbKi, m) END DO - DO l = 1,p%nCpldCons(iTurb) ! keeping this one simple for now, positioning at whatever is specified by glue code <<< + DO l = 1,p%nCpldPoints(iTurb) ! keeping this one simple for now, positioning at whatever is specified by glue code <<< J = J + 1 ! set reference position as per input file <<< what about turbine positions in array? - rRef(1:3) = m%ConnectList(m%CpldConIs(l,iTurb))%r + rRef(1:3) = m%PointList(m%CpldPointIs(l,iTurb))%r CALL MeshPositionNode(u%CoupledKinematics(iTurb), J, rRef(1:3), ErrStat2, ErrMsg2) ! calculate initial point relative position, adjusted due to initial platform rotations and translations <<< could convert to array math @@ -1822,13 +1822,13 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er u%CoupledKinematics(iTurb)%TranslationDisp(3,J) = InitInp%PtfmInit(3,iTurb) + OrMat(1,3)*rRef(1) + OrMat(2,3)*rRef(2) + OrMat(3,3)*rRef(3) - rRef(3) ! set absolute initial positions in MoorDyn - m%ConnectList(m%CpldConIs(l,iTurb))%r = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb) + m%PointList(m%CpldPointIs(l,iTurb))%r = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb) CALL MeshConstructElement(u%CoupledKinematics(iTurb), ELEMENT_POINT, ErrStat2, ErrMsg2, J) ! lastly, do this to set the attached line endpoint positions: rRefDub = rRef(1:3) - CALL Connect_SetKinematics(m%ConnectList(m%CpldConIs(l,iTurb)), rRefDub, m%zeros6(1:3), m%zeros6(1:3), 0.0_DbKi, m) + CALL Point_SetKinematics(m%PointList(m%CpldPointIs(l,iTurb)), rRefDub, m%zeros6(1:3), m%zeros6(1:3), 0.0_DbKi, m) END DO CALL CheckError( ErrStat2, ErrMsg2 ) @@ -1949,9 +1949,9 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er CALL Rod_Initialize(m%RodList(m%FreeRodIs(l)), x%states(m%RodStateIs1(l):m%RodStateIsN(l)), m) END DO - ! Go through independent connections (Connects) and write the coordinates to the state vector and set positions of attached line ends - DO l = 1, p%nFreeCons - CALL Connect_Initialize(m%ConnectList(m%FreeConIs(l)), x%states(m%ConStateIs1(l) : m%conStateIsN(l)), m) + ! Go through independent points (Points) and write the coordinates to the state vector and set positions of attached line ends + DO l = 1, p%nFreePoints + CALL Point_Initialize(m%PointList(m%FreePointIs(l)), x%states(m%PointStateIs1(l) : m%pointStateIsN(l)), m) END DO @@ -1960,9 +1960,9 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er N = m%LineList(l)%N ! for convenience - ! ! set end node positions and velocities from connect objects - ! m%LineList(l)%r(:,N) = m%ConnectList(m%LineList(l)%FairConnect)%r - ! m%LineList(l)%r(:,0) = m%ConnectList(m%LineList(l)%AnchConnect)%r + ! ! set end node positions and velocities from point objects + ! m%LineList(l)%r(:,N) = m%PointList(m%LineList(l)%FairPoint)%r + ! m%LineList(l)%r(:,0) = m%PointList(m%LineList(l)%AnchPoint)%r ! m%LineList(l)%rd(:,N) = (/ 0.0, 0.0, 0.0 /) ! set anchor end velocities to zero ! m%LineList(l)%rd(:,0) = (/ 0.0, 0.0, 0.0 /) ! set fairlead end velocities to zero @@ -2040,9 +2040,9 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er END DO write(p%UnLog, '(A)' ) " Points:" - DO l = 1,p%nFreeCons + DO l = 1,p%nFreePoints write(p%UnLog, '(A)' ) " Point"//trim(num2lstr(l))//":" - ! m%ConnectList(l) + ! m%PointList(l) END DO write(p%UnLog, '(A)' ) " Lines:" @@ -2250,12 +2250,12 @@ SUBROUTINE CheckError(ErrID,Msg) IF ( ErrStat >= AbortErrLev ) THEN - IF (ALLOCATED(m%CpldConIs )) DEALLOCATE(m%CpldConIs ) - IF (ALLOCATED(m%FreeConIs )) DEALLOCATE(m%FreeConIs ) + IF (ALLOCATED(m%CpldPointIs )) DEALLOCATE(m%CpldPointIs ) + IF (ALLOCATED(m%FreePointIs )) DEALLOCATE(m%FreePointIs ) IF (ALLOCATED(m%LineStateIs1 )) DEALLOCATE(m%LineStateIs1 ) IF (ALLOCATED(m%LineStateIsN )) DEALLOCATE(m%LineStateIsN ) - IF (ALLOCATED(m%ConStateIs1 )) DEALLOCATE(m%ConStateIs1 ) - IF (ALLOCATED(m%ConStateIsN )) DEALLOCATE(m%ConStateIsN ) + IF (ALLOCATED(m%PointStateIs1 )) DEALLOCATE(m%PointStateIs1 ) + IF (ALLOCATED(m%PointStateIsN )) DEALLOCATE(m%PointStateIsN ) IF (ALLOCATED(x%states )) DEALLOCATE(x%states ) IF (ALLOCATED(FairTensIC )) DEALLOCATE(FairTensIC ) @@ -2338,10 +2338,10 @@ SUBROUTINE MD_UpdateStates( t, n, u, t_array, p, x, xd, z, other, m, ErrStat, Er ! ! ! ! go through fairleads and apply motions from driver -! DO I = 1, p%nCpldCons +! DO I = 1, p%nCpldPoints ! DO J = 1,3 -! m%ConnectList(m%CpldConIs(I))%r(J) = u_interp%PtFairleadDisplacement%Position(J,I) + u_interp%PtFairleadDisplacement%TranslationDisp(J,I) -! m%ConnectList(m%CpldConIs(I))%rd(J) = u_interp%PtFairleadDisplacement%TranslationVel(J,I) ! is this right? <<< +! m%PointList(m%CpldPointIs(I))%r(J) = u_interp%PtFairleadDisplacement%Position(J,I) + u_interp%PtFairleadDisplacement%TranslationDisp(J,I) +! m%PointList(m%CpldPointIs(I))%rd(J) = u_interp%PtFairleadDisplacement%TranslationVel(J,I) ! is this right? <<< ! END DO ! END DO ! @@ -2478,10 +2478,10 @@ SUBROUTINE MD_CalcOutput( t, u, p, x, xd, z, other, y, m, ErrStat, ErrMsg ) ! below updated to make sure outputs are current (based on provided x and u) - similar to what's in UpdateStates ! ! go through fairleads and apply motions from driver - ! DO I = 1, p%nCpldCons + ! DO I = 1, p%nCpldPoints ! DO J = 1,3 - ! m%ConnectList(m%CpldConIs(I))%r(J) = u%CoupledKinematics%Position(J,I) + u%CoupledKinematics%TranslationDisp(J,I) - ! m%ConnectList(m%CpldConIs(I))%rd(J) = u%CoupledKinematics%TranslationVel(J,I) ! is this right? <<< + ! m%PointList(m%CpldPointIs(I))%r(J) = u%CoupledKinematics%Position(J,I) + u%CoupledKinematics%TranslationDisp(J,I) + ! m%PointList(m%CpldPointIs(I))%rd(J) = u%CoupledKinematics%TranslationVel(J,I) ! is this right? <<< ! END DO ! END DO @@ -2508,11 +2508,11 @@ SUBROUTINE MD_CalcOutput( t, u, p, x, xd, z, other, y, m, ErrStat, ErrMsg ) ! END DO ! END DO ! ! Point reference point coordinates - ! DO I = 1, p%nConnects + ! DO I = 1, p%nPoints ! J = J + 1 - ! m%ConnectList(I)%U = u%U(:,J) - ! m%ConnectList(I)%Ud = u%Ud(:,J) - ! m%ConnectList(I)%zeta = u%zeta(J) + ! m%PointList(I)%U = u%U(:,J) + ! m%PointList(I)%Ud = u%Ud(:,J) + ! m%PointList(I)%zeta = u%zeta(J) ! END DO ! ! Line internal node coordinates ! DO I = 1, p%nLines @@ -2531,10 +2531,10 @@ SUBROUTINE MD_CalcOutput( t, u, p, x, xd, z, other, y, m, ErrStat, ErrMsg ) ! call CalcContStateDeriv in order to run model and calculate dynamics with provided x and u CALL MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, m%xdTemp, ErrStat, ErrMsg ) - ! ! assign net force on fairlead Connects to the fairlead force output mesh - ! DO i = 1, p%nCpldCons + ! ! assign net force on fairlead Points to the fairlead force output mesh + ! DO i = 1, p%nCpldPoints ! DO J=1,3 - ! y%PtFairleadLoad%Force(J,I) = m%ConnectList(m%CpldConIs(I))%Fnet(J) + ! y%PtFairleadLoad%Force(J,I) = m%PointList(m%CpldPointIs(I))%Fnet(J) ! END DO ! END DO @@ -2557,9 +2557,9 @@ SUBROUTINE MD_CalcOutput( t, u, p, x, xd, z, other, y, m, ErrStat, ErrMsg ) y%CoupledLoads(iTurb)%Moment(:,J) = F6net(4:6) END DO - DO l = 1,p%nCpldCons(iTurb) + DO l = 1,p%nCpldPoints(iTurb) J = J + 1 - CALL Connect_GetCoupledForce(m%ConnectList(m%CpldConIs(l,iTurb)), F6net(1:3), m, p) + CALL Point_GetCoupledForce(m%PointList(m%CpldPointIs(l,iTurb)), F6net(1:3), m, p) y%CoupledLoads(iTurb)%Force(:,J) = F6net(1:3) END DO @@ -2581,9 +2581,9 @@ SUBROUTINE MD_CalcOutput( t, u, p, x, xd, z, other, y, m, ErrStat, ErrMsg ) ! END DO ! END DO ! ! Point reference point coordinates - ! DO I = 1, p%nConnects + ! DO I = 1, p%nPoints ! J = J + 1 - ! y%rAll(:,J) = m%ConnectList(I)%r + ! y%rAll(:,J) = m%PointList(I)%r ! END DO ! ! Line internal node coordinates ! DO I = 1, p%nLines @@ -2658,8 +2658,8 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er INTEGER(IntKi) :: J ! index INTEGER(IntKi) :: K ! index INTEGER(IntKi) :: iTurb ! index - INTEGER(IntKi) :: Istart ! start index of line/connect in state vector - INTEGER(IntKi) :: Iend ! end index of line/connect in state vector + INTEGER(IntKi) :: Istart ! start index of line/point in state vector + INTEGER(IntKi) :: Iend ! end index of line/point in state vector REAL(DbKi) :: temp(3) ! temporary for passing kinematics @@ -2685,21 +2685,21 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er IF ( ErrStat >= AbortErrLev ) RETURN END IF - ! clear connection force and mass values updateFairlead( t ); <<<< manually set anchored connection stuff for now here + !GroundBody->updateFairlead( t ); <<<< manually set anchored point stuff for now here r6_in = 0.0_DbKi v6_in = 0.0_DbKi CALL Body_SetKinematics(m%GroundBody, r6_in, v6_in, m%zeros6, t, m) @@ -2742,13 +2742,13 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er END DO ! any coupled points (type -1) - DO l = 1, p%nCpldCons(iTurb) + DO l = 1, p%nCpldPoints(iTurb) J = J + 1 r_in = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb) rd_in = u%CoupledKinematics(iTurb)%TranslationVel(:,J) a_in(1:3) = u%CoupledKinematics(iTurb)%TranslationAcc(:,J) - CALL Connect_SetKinematics(m%ConnectList(m%CpldConIs(l,iTurb)), r_in, rd_in, a_in, t, m) + CALL Point_SetKinematics(m%PointList(m%CpldPointIs(l,iTurb)), r_in, rd_in, a_in, t, m) !print "(f8.5, f12.6, f12.6, f8.4, f8.4, f8.4, f8.4)", t, r_in(1), r_in(3), rd_in(1), rd_in(3), a_in(1), a_in(3) @@ -2817,11 +2817,11 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er ! END DO ! END DO ! ! Point reference point coordinates - ! DO I = 1, p%nConnects + ! DO I = 1, p%nPoints ! J = J + 1 - ! m%ConnectList(I)%U = u%U(:,J) - ! m%ConnectList(I)%Ud = u%Ud(:,J) - ! m%ConnectList(I)%zeta = u%zeta(J) + ! m%PointList(I)%U = u%U(:,J) + ! m%PointList(I)%Ud = u%Ud(:,J) + ! m%PointList(I)%zeta = u%zeta(J) ! END DO ! ! Line internal node coordinates ! DO I = 1, p%nLines @@ -2838,7 +2838,7 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er ! independent or semi-independent things with their own states... - ! give Bodies latest state variables (kinematics will also be assigned to dependent connections and rods, and thus line ends) + ! give Bodies latest state variables (kinematics will also be assigned to dependent points and rods, and thus line ends) DO l = 1,p%nFreeBodies CALL Body_SetState(m%BodyList(m%FreeBodyIs(l)), x%states(m%BodyStateIs1(l):m%BodyStateIsN(l)), t, m) END DO @@ -2848,11 +2848,11 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er CALL Rod_SetState(m%RodList(m%FreeRodIs(l)), x%states(m%RodStateIs1(l):m%RodStateIsN(l)), t, m) END DO - ! give Connects (independent connections) latest state variable values (kinematics will also be assigned to attached line ends) - DO l = 1,p%nFreeCons - ! Print *, "calling SetState for free connection, con#", m%FreeConIs(l), " with state range: ", m%ConStateIs1(l), "-", m%ConStateIsN(l) + ! give Points (independent points) latest state variable values (kinematics will also be assigned to attached line ends) + DO l = 1,p%nFreePoints + ! Print *, "calling SetState for free point, point#", m%FreePointIs(l), " with state range: ", m%PointStateIs1(l), "-", m%PointStateIsN(l) !K=K+1 - CALL Connect_SetState(m%ConnectList(m%FreeConIs(l)), x%states(m%ConStateIs1(l):m%ConStateIsN(l)), t, m) + CALL Point_SetState(m%PointList(m%FreePointIs(l)), x%states(m%PointStateIs1(l):m%PointStateIsN(l)), t, m) END DO ! give Lines latest state variable values for internal nodes @@ -2862,15 +2862,15 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er ! calculate dynamics of free objects (will also calculate forces (doRHS()) from any child/dependent objects)... - ! calculate line dynamics (and calculate line forces and masses attributed to connections) + ! calculate line dynamics (and calculate line forces and masses attributed to points) DO l = 1,p%nLines CALL Line_GetStateDeriv(m%LineList(l), dxdt%states(m%LineStateIs1(l):m%LineStateIsN(l)), m, p) !dt might also be passed for fancy friction models END DO - ! calculate connect dynamics (including contributions from attached lines - ! as well as hydrodynamic forces etc. on connect object itself if applicable) - DO l = 1,p%nFreeCons - CALL Connect_GetStateDeriv(m%ConnectList(m%FreeConIs(l)), dxdt%states(m%ConStateIs1(l):m%ConStateIsN(l)), m, p) + ! calculate point dynamics (including contributions from attached lines + ! as well as hydrodynamic forces etc. on point object itself if applicable) + DO l = 1,p%nFreePoints + CALL Point_GetStateDeriv(m%PointList(m%FreePointIs(l)), dxdt%states(m%PointStateIs1(l):m%PointStateIsN(l)), m, p) END DO ! calculate dynamics of independent Rods @@ -2889,12 +2889,12 @@ SUBROUTINE MD_CalcContStateDeriv( t, u, p, x, xd, z, other, m, dxdt, ErrStat, Er ! note: can do this in any order since there are no dependencies among coupled objects DO iTurb = 1,p%nTurbines - DO l = 1,p%nCpldCons(iTurb) + DO l = 1,p%nCpldPoints(iTurb) ! >>>>>>>> here we should pass along accelerations and include inertial loads in the calculation!!! <<>> below should no longer be necessary thanks to using ExtrapInterp of u(:) within the mooring time stepping loop.. <<< ! ! update Fairlead positions by integrating velocity and last position (do this AFTER the processing of the time step rather than before) - ! DO J = 1, p%nCpldCons + ! DO J = 1, p%nCpldPoints ! DO K = 1, 3 - ! m%ConnectList(m%CpldConIs(J))%r(K) = m%ConnectList(m%CpldConIs(J))%r(K) + m%ConnectList(m%CpldConIs(J))%rd(K)*dtM + ! m%PointList(m%CpldPointIs(J))%r(K) = m%PointList(m%CpldPointIs(J))%r(K) + m%PointList(m%CpldPointIs(J))%rd(K)*dtM ! END DO ! END DO @@ -3182,7 +3182,7 @@ END SUBROUTINE TimeStep !-------------------------------------------------------------- -! Connection-Specific Subroutines +! Point-Specific Subroutines !-------------------------------------------------------------- @@ -3777,16 +3777,16 @@ SUBROUTINE Init_Jacobian_x() end if END DO - ! Free Connnections - DO l = 1,p%nFreeCons ! Point m%ConnectList(m%FreeConIs(l)) - ! corresponds to state indices: (m%ConStateIs1(l)+3:m%ConStateIs1(l)+5) + ! Free Points + DO l = 1,p%nFreePoints ! Point m%PointList(m%FreePointIs(l)) + ! corresponds to state indices: (m%PointStateIs1(l)+3:m%PointStateIs1(l)+5) p%dx(idx+1:idx+3) = dl_slack_min ! point displacement [m] - InitOut%LinNames_x(idx+1) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Px, m' - InitOut%LinNames_x(idx+2) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Py, m' - InitOut%LinNames_x(idx+3) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Pz, m' - p%dxIdx_map2_xStateIdx(idx+1) = m%ConStateIs1(l)+3 ! x%state index for Px - p%dxIdx_map2_xStateIdx(idx+2) = m%ConStateIs1(l)+4 ! x%state index for Py - p%dxIdx_map2_xStateIdx(idx+3) = m%ConStateIs1(l)+5 ! x%state index for Pz + InitOut%LinNames_x(idx+1) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Px, m' + InitOut%LinNames_x(idx+2) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Py, m' + InitOut%LinNames_x(idx+3) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Pz, m' + p%dxIdx_map2_xStateIdx(idx+1) = m%PointStateIs1(l)+3 ! x%state index for Px + p%dxIdx_map2_xStateIdx(idx+2) = m%PointStateIs1(l)+4 ! x%state index for Py + p%dxIdx_map2_xStateIdx(idx+3) = m%PointStateIs1(l)+5 ! x%state index for Pz idx = idx + 3 END DO @@ -3861,16 +3861,16 @@ SUBROUTINE Init_Jacobian_x() end if END DO - ! Free Connnections - DO l = 1,p%nFreeCons ! Point m%ConnectList(m%FreeConIs(l)) - ! corresponds to state indices: (m%ConStateIs1(l):m%ConStateIs1(l)+2) + ! Free Points + DO l = 1,p%nFreePoints ! Point m%PointList(m%FreePointIs(l)) + ! corresponds to state indices: (m%PointStateIs1(l):m%PointStateIs1(l)+2) p%dx(idx+1:idx+3) = 0.1 ! point translational velocity [m/s] - InitOut%LinNames_x(idx+1) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Vx, m/s' - InitOut%LinNames_x(idx+2) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Vy, m/s' - InitOut%LinNames_x(idx+3) = 'Point '//trim(num2lstr(m%FreeConIs(l)))//' Vz, m/s' - p%dxIdx_map2_xStateIdx(idx+1) = m%ConStateIs1(l)+0 ! x%state index for Vx - p%dxIdx_map2_xStateIdx(idx+2) = m%ConStateIs1(l)+1 ! x%state index for Vy - p%dxIdx_map2_xStateIdx(idx+3) = m%ConStateIs1(l)+2 ! x%state index for Vz + InitOut%LinNames_x(idx+1) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Vx, m/s' + InitOut%LinNames_x(idx+2) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Vy, m/s' + InitOut%LinNames_x(idx+3) = 'Point '//trim(num2lstr(m%FreePointIs(l)))//' Vz, m/s' + p%dxIdx_map2_xStateIdx(idx+1) = m%PointStateIs1(l)+0 ! x%state index for Vx + p%dxIdx_map2_xStateIdx(idx+2) = m%PointStateIs1(l)+1 ! x%state index for Vy + p%dxIdx_map2_xStateIdx(idx+3) = m%PointStateIs1(l)+2 ! x%state index for Vz idx = idx + 3 END DO diff --git a/modules/moordyn/src/MoorDyn_Body.f90 b/modules/moordyn/src/MoorDyn_Body.f90 index c34e21c162..49b6e8c430 100644 --- a/modules/moordyn/src/MoorDyn_Body.f90 +++ b/modules/moordyn/src/MoorDyn_Body.f90 @@ -25,7 +25,7 @@ MODULE MoorDyn_Body USE NWTC_Library USE MoorDyn_Misc !USE MoorDyn_Line, only : Line_SetEndKinematics, Line_GetEndStuff - USE MoorDyn_Point, only : Connect_SetKinematics, Connect_GetNetForceAndMass + USE MoorDyn_Point, only : Point_SetKinematics, Point_GetNetForceAndMass USE MoorDyn_Rod, only : Rod_Initialize, Rod_SetKinematics, Rod_GetNetForceAndMass IMPLICIT NONE @@ -43,7 +43,7 @@ MODULE MoorDyn_Body PUBLIC :: Body_GetStateDeriv PUBLIC :: Body_DoRHS PUBLIC :: Body_GetCoupledForce - PUBLIC :: Body_AddConnect + PUBLIC :: Body_AddPoint PUBLIC :: Body_AddRod @@ -134,7 +134,7 @@ END SUBROUTINE Body_Setup ! if (m%RodList(Body%attachedR(l))%typeNum == 2) CALL Rod_Initialize(m%RodList(Body%attachedR(l)), dummyStates, m%LineList) ! END DO ! -! ! Note: Connections don't need any initialization +! ! Note: Points don't need any initialization ! ! END SUBROUTINE Body_InitializeUnfree ! !-------------------------------------------------------------- @@ -157,7 +157,7 @@ SUBROUTINE Body_Initialize(Body, states, m) states(1:6 ) = Body%v6 - ! set positions of any dependent connections and rods now (before they are initialized) + ! set positions of any dependent points and rods now (before they are initialized) CALL Body_SetDependentKin(Body, 0.0_DbKi, m) ! If any Rod is fixed to the body (not pinned), initialize it now because otherwise it won't be initialized @@ -165,7 +165,7 @@ SUBROUTINE Body_Initialize(Body, states, m) if (m%RodList(Body%attachedR(l))%typeNum == 2) CALL Rod_Initialize(m%RodList(Body%attachedR(l)), dummyStates, m) END DO - ! Note: Connections don't need any initialization + ! Note: Points don't need any initialization END SUBROUTINE Body_Initialize !-------------------------------------------------------------- @@ -181,7 +181,7 @@ SUBROUTINE Body_InitializeUnfree(Body, m) REAL(DbKi) :: dummyStates(12) ! dummy vector to mimic states when initializing a rigidly attached rod - ! set positions of any dependent connections and rods now (before they are initialized) + ! set positions of any dependent points and rods now (before they are initialized) CALL Body_SetDependentKin(Body, 0.0_DbKi, m) ! If any Rod is fixed to the body (not pinned), initialize it now because otherwise it won't be initialized @@ -189,7 +189,7 @@ SUBROUTINE Body_InitializeUnfree(Body, m) if (m%RodList(Body%attachedR(l))%typeNum == 2) CALL Rod_Initialize(m%RodList(Body%attachedR(l)), dummyStates, m) END DO - ! Note: Connections don't need any initialization + ! Note: Points don't need any initialization END SUBROUTINE Body_InitializeUnfree !-------------------------------------------------------------- @@ -206,7 +206,7 @@ SUBROUTINE Body_SetKinematics(Body, r_in, v_in, a_in, t, m) Real(DbKi), INTENT(IN ) :: v_in(6) ! 6-DOF velocity Real(DbKi), INTENT(IN ) :: a_in(6) ! 6-DOF acceleration (only used for coupled rods) Real(DbKi), INTENT(IN ) :: t ! instantaneous time - TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Connections) + TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Points) INTEGER(IntKi) :: l @@ -259,26 +259,26 @@ SUBROUTINE Body_SetState(Body, X, t, m) Body%v6 = X(1:6) ! get velocities - ! set positions of any dependent connections and rods + ! set positions of any dependent points and rods CALL Body_SetDependentKin(Body, t, m) END SUBROUTINE Body_SetState !-------------------------------------------------------------- - ! set the states (positions and velocities) of any connects or rods that are part of this body + ! set the states (positions and velocities) of any points or rods that are part of this body ! also computes the orientation matrix (never skip this sub!) !-------------------------------------------------------------- SUBROUTINE Body_SetDependentKin(Body, t, m) Type(MD_Body), INTENT(INOUT) :: Body ! the Bodyion object REAL(DbKi), INTENT(IN ) :: t - TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Connections) + TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Points) INTEGER(IntKi) :: l ! index of attached objects - Real(DbKi) :: rConnect(3) - Real(DbKi) :: rdConnect(3) + Real(DbKi) :: rPoint(3) + Real(DbKi) :: rdPoint(3) Real(DbKi) :: rRod(6) Real(DbKi) :: vRod(6) Real(DbKi) :: aRod(6) @@ -289,15 +289,15 @@ SUBROUTINE Body_SetDependentKin(Body, t, m) !CALL SmllRotTrans('', Body%r6(4), Body%r6(5), Body%r6(6), Body%TransMat, '', ErrStat2, ErrMsg2) Body%OrMat = TRANSPOSE( EulerConstruct( Body%r6(4:6) ) ) ! full Euler angle approach <<<< need to check order - ! set kinematics of any dependent connections + ! set kinematics of any dependent points do l = 1,Body%nAttachedC - CALL transformKinematics(Body%rConnectRel(:,l), Body%r6, Body%OrMat, Body%v6, rConnect, rdConnect) !<<< should double check this function + CALL transformKinematics(Body%rPointRel(:,l), Body%r6, Body%OrMat, Body%v6, rPoint, rdPoint) !<<< should double check this function ! >>> need to add acceleration terms here too? <<< - ! pass above to the connection and get it to calculate the forces - CALL Connect_SetKinematics( m%ConnectList(Body%attachedC(l)), rConnect, rdConnect, m%zeros6(1:3), t, m) + ! pass above to the point and get it to calculate the forces + CALL Point_SetKinematics( m%PointList(Body%attachedC(l)), rPoint, rdPoint, m%zeros6(1:3), t, m) end do ! set kinematics of any dependent Rods @@ -424,11 +424,11 @@ SUBROUTINE Body_DoRHS(Body, m, p) - ! Get contributions from any dependent connections + ! Get contributions from any dependent points do l = 1,Body%nAttachedC - ! get net force and mass from Connection on body ref point (global orientation) - CALL Connect_GetNetForceAndMass( m%ConnectList(Body%attachedC(l)), Body%r6(1:3), F6_i, M6_i, m, p) + ! get net force and mass from Point on body ref point (global orientation) + CALL Point_GetNetForceAndMass( m%PointList(Body%attachedC(l)), Body%r6(1:3), F6_i, M6_i, m, p) if (ABS(F6_i(5)) > 1.0E12) then print *, "Warning: extreme pitch moment from body-attached Point ", l @@ -488,33 +488,33 @@ END SUBROUTINE Body_GetCoupledForce - ! this function handles assigning a connection to a body + ! this function handles assigning a point to a body !-------------------------------------------------------------- - SUBROUTINE Body_AddConnect(Body, connectID, coords) + SUBROUTINE Body_AddPoint(Body, pointID, coords) - Type(MD_Body), INTENT(INOUT) :: Body ! the Connection object - Integer(IntKi), INTENT(IN ) :: connectID + Type(MD_Body), INTENT(INOUT) :: Body ! the Point object + Integer(IntKi), INTENT(IN ) :: pointID REAL(DbKi), INTENT(IN ) :: coords(3) - IF (wordy > 0) Print*, "C", connectID, "->B", Body%IdNum + IF (wordy > 0) Print*, "P", pointID, "->B", Body%IdNum IF(Body%nAttachedC < 30) THEN ! this is currently just a maximum imposed by a fixed array size. could be improved. - Body%nAttachedC = Body%nAttachedC + 1 ! increment the number connected - Body%AttachedC(Body%nAttachedC) = connectID - Body%rConnectRel(:,Body%nAttachedC) = coords ! store relative position of connect on body + Body%nAttachedC = Body%nAttachedC + 1 ! increment the number pointed + Body%AttachedC(Body%nAttachedC) = pointID + Body%rPointRel(:,Body%nAttachedC) = coords ! store relative position of point on body ELSE Print*, "too many Points attached to Body ", Body%IdNum, " in MoorDyn!" END IF - END SUBROUTINE Body_AddConnect + END SUBROUTINE Body_AddPoint ! this function handles assigning a rod to a body !-------------------------------------------------------------- SUBROUTINE Body_AddRod(Body, rodID, coords) - Type(MD_Body), INTENT(INOUT) :: Body ! the Connection object + Type(MD_Body), INTENT(INOUT) :: Body ! the Point object Integer(IntKi), INTENT(IN ) :: rodID REAL(DbKi), INTENT(IN ) :: coords(6) ! positions of rod ends A and B relative to body diff --git a/modules/moordyn/src/MoorDyn_Driver.f90 b/modules/moordyn/src/MoorDyn_Driver.f90 index 9b370d8eb7..83e2e5e65b 100644 --- a/modules/moordyn/src/MoorDyn_Driver.f90 +++ b/modules/moordyn/src/MoorDyn_Driver.f90 @@ -249,7 +249,7 @@ PROGRAM MoorDyn_Driver endif do iTurb = 1, MD_p%nTurbines - ncIn = ncIn + MD_p%nCpldBodies(iTurb)*6 + MD_p%nCpldRods(iTurb)*6 + MD_p%nCpldCons(iTurb)*3 + ncIn = ncIn + MD_p%nCpldBodies(iTurb)*6 + MD_p%nCpldRods(iTurb)*6 + MD_p%nCpldPoints(iTurb)*3 end do call WrScr('MoorDyn has '//trim(num2lstr(ncIn))//' coupled DOFs and/or active-tensioned inputs.') @@ -519,7 +519,7 @@ PROGRAM MoorDyn_Driver END DO ! any coupled points (type -1) - DO l = 1, MD_p%nCpldCons(iTurb) + DO l = 1, MD_p%nCpldPoints(iTurb) MD_u(1)%CoupledKinematics(iTurb)%TranslationDisp(:,K) = r_in(i, J:J+2) - MD_u(1)%CoupledKinematics(iTurb)%Position(:,K) - MD_p%TurbineRefPos(:,iTurb) MD_u(1)%CoupledKinematics(iTurb)%TranslationVel( :,K) = rd_in(i, J:J+2) @@ -608,7 +608,7 @@ PROGRAM MoorDyn_Driver END DO ! any coupled points (type -1) - DO l = 1, MD_p%nCpldCons(iTurb) + DO l = 1, MD_p%nCpldPoints(iTurb) MD_u(1)%CoupledKinematics(iTurb)%TranslationDisp(:,K) = r_in(i, J:J+2) - MD_u(1)%CoupledKinematics(iTurb)%Position(:,K) - MD_p%TurbineRefPos(:,iTurb) MD_u(1)%CoupledKinematics(iTurb)%TranslationVel( :,K) = rd_in(i, J:J+2) diff --git a/modules/moordyn/src/MoorDyn_IO.f90 b/modules/moordyn/src/MoorDyn_IO.f90 index 14d93ff6be..d4b5e8a767 100644 --- a/modules/moordyn/src/MoorDyn_IO.f90 +++ b/modules/moordyn/src/MoorDyn_IO.f90 @@ -42,12 +42,12 @@ MODULE MoorDyn_IO ! Each output channel is described by the following fields: ! Name - (string) what appears at the top of the output column ! Units - (string) selected from UnitList (see below) based on index QType - ! OType - (int) the type of object the output is from. 1=line, 2=connect (0=invalid) - ! ObjID - (int) the ID number of the line or connect + ! OType - (int) the type of object the output is from. 1=line, 2=point (0=invalid) + ! ObjID - (int) the ID number of the line or point ! QType - (int) the type of quantity to output. 0=tension, 1=x pos, etc. see the parameters below ! NodeID - (int) the ID number of the node of the output quantity - ! These are the "OTypes": 1=Line, 2=Connect, 3=Rod, 4=Body + ! These are the "OTypes": 1=Line, 2=point, 3=Rod, 4=Body ! Indices for computing output channels: - customized for the MD_OutParmType approach ! these are the "QTypes" @@ -55,32 +55,43 @@ MODULE MoorDyn_IO INTEGER, PARAMETER :: PosX = 1 INTEGER, PARAMETER :: PosY = 2 INTEGER, PARAMETER :: PosZ = 3 - INTEGER, PARAMETER :: VelX = 4 - INTEGER, PARAMETER :: VelY = 5 - INTEGER, PARAMETER :: VelZ = 6 - INTEGER, PARAMETER :: AccX = 7 - INTEGER, PARAMETER :: AccY = 8 - INTEGER, PARAMETER :: AccZ = 9 - INTEGER, PARAMETER :: Ten = 10 - INTEGER, PARAMETER :: FX = 11 - INTEGER, PARAMETER :: FY = 12 - INTEGER, PARAMETER :: FZ = 13 - INTEGER, PARAMETER :: MX = 14 - INTEGER, PARAMETER :: MY = 15 - INTEGER, PARAMETER :: MZ = 16 - INTEGER, PARAMETER :: Pitch = 17 - INTEGER, PARAMETER :: Roll = 18 - INTEGER, PARAMETER :: Yaw = 19 - INTEGER, PARAMETER :: Sub = 20 + INTEGER, PARAMETER :: RotX = 4 + INTEGER, PARAMETER :: RotY = 5 + INTEGER, PARAMETER :: RotZ = 6 + INTEGER, PARAMETER :: VelX = 7 + INTEGER, PARAMETER :: VelY = 8 + INTEGER, PARAMETER :: VelZ = 9 + INTEGER, PARAMETER :: RVelX = 10 + INTEGER, PARAMETER :: RVelY = 11 + INTEGER, PARAMETER :: RVelZ = 12 + INTEGER, PARAMETER :: AccX = 13 + INTEGER, PARAMETER :: AccY = 14 + INTEGER, PARAMETER :: AccZ = 15 + INTEGER, PARAMETER :: RAccX = 16 + INTEGER, PARAMETER :: RAccY = 17 + INTEGER, PARAMETER :: RAccZ = 18 + INTEGER, PARAMETER :: Ten = 19 + INTEGER, PARAMETER :: FX = 20 + INTEGER, PARAMETER :: FY = 21 + INTEGER, PARAMETER :: FZ = 22 + INTEGER, PARAMETER :: MX = 23 + INTEGER, PARAMETER :: MY = 24 + INTEGER, PARAMETER :: MZ = 25 + INTEGER, PARAMETER :: Sub = 26 + INTEGER, PARAMETER :: TenA = 27 + INTEGER, PARAMETER :: TenB = 28 + ! List of units corresponding to the quantities parameters for QTypes - CHARACTER(ChanLen), PARAMETER :: UnitList(0:20) = (/ & + CHARACTER(ChanLen), PARAMETER :: UnitList(0:26) = (/ & "(s) ","(m) ","(m) ","(m) ", & + "(deg) ","(deg) ","(deg) ", & "(m/s) ","(m/s) ","(m/s) ", & + "(deg/s) ","(deg/s) ","(deg/s) ", & "(m/s2) ","(m/s2) ","(m/s2) ", & + "(deg/s2) ","(deg/s2) ","(deg/s2) ", & "(N) ","(N) ","(N) ","(N) ", & - "(Nm) ","(Nm) ","(Nm) ", & - "(deg) ","(deg) ","(deg) ","(frac) "/) + "(Nm) ","(Nm) ","(Nm) ","(frac) "/) CHARACTER(28), PARAMETER :: OutPFmt = "( I4, 3X,A 10,1 X, A10 )" ! Output format parameter output list. CHARACTER(28), PARAMETER :: OutSFmt = "ES10.3E2" @@ -89,9 +100,9 @@ MODULE MoorDyn_IO ! output naming scheme is as ! examples: ! FairTen1, AnchTen1 - ! Con1pX - ! Con3vY (connection 3, y velocity) - ! L2N4pX (line 2, node 4, x position) + ! POINT1PX + ! P3VY (Point 3, y velocity) + ! L2N4PX (line 2, node 4, x position) ! --------------------------------------------------------------------------------------------------------- @@ -323,7 +334,7 @@ SUBROUTINE DecomposeString(outWord, let1, num1, let2, num2, let3) CHARACTER(ChanLen) :: OutListTmp ! A string to temporarily hold OutList(I), the name of each output channel CHARACTER(ChanLen) :: qVal ! quantity type string to match to list of valid options - INTEGER :: oID ! ID number of connect or line object + INTEGER :: oID ! ID number of point or line object INTEGER :: nID ! ID number of node object INTEGER :: i1 = 0 ! indices of start of numbers or letters in OutListTmp string, for parsing INTEGER :: i2 = 0 @@ -415,7 +426,7 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) CHARACTER(ChanLen) :: OutListTmp ! A string to temporarily hold OutList(I), the name of each output channel CHARACTER(ChanLen) :: qVal ! quantity type string to match to list of valid options - INTEGER :: oID ! ID number of connect or line object + INTEGER :: oID ! ID number of point or line object INTEGER :: nID ! ID number of node object INTEGER :: i1,i2,i3,i4 ! indices of start of numbers or letters in OutListTmp string, for parsing @@ -510,6 +521,16 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) ! more general case ELSE + ! object number + IF (num1/=" ") THEN + READ (num1,*) oID + p%OutParam(I)%ObjID = oID ! line or point ID number + ELSE + CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid + CALL WrScr('Warning: invalid output specifier '//trim(OutListTmp)//'. Object ID missing.') + CYCLE + END IF + ! what object type? ! Line case @@ -519,23 +540,40 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) IF (num2/=" ") THEN READ (num2,*) nID ! node or segment ID p%OutParam(I)%NodeID = nID + qVal = let3 ! quantity type string + ELSE IF (let2 == 'TENA' .OR. let2 == 'TA') THEN + p%OutParam(I)%NodeID = 0 + qVal = let2 + ELSE IF (let2 == 'TENB' .OR. let2 == 'TB') THEN + p%OutParam(I)%NodeID = m%LineList(p%OutParam(I)%ObjID)%N + qVal = let2 ELSE CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid - CALL WrScr('Warning: invalid output specifier '//trim(OutListTmp)//'. Line ID or Node ID missing.') + CALL WrScr('Warning: invalid output specifier '//trim(OutListTmp)//'. Line ID or Node ID missing or incorrect tension flag.') CYCLE END IF - qVal = let3 ! quantity type string - ! Connect case - ELSE IF (let1(1:1) == 'C') THEN ! Look for C?xxx or Con?xxx - p%OutParam(I)%OType = 2 ! Connect object type + ! Point case + ELSE IF (let1(1:1) == 'P') THEN ! Look for P?xxx or Point?xxx + p%OutParam(I)%OType = 2 ! Point object type qVal = let2 ! quantity type string ! Rod case ELSE IF (let1(1:1) == 'R') THEN ! Look for R?xxx or Rod?xxx p%OutParam(I)%OType = 3 ! Rod object type - IF (LEN_TRIM(let3)== 0) THEN ! No third character cluster indicates this is a whole-rod channel - p%OutParam(I)%NodeID = 0 + IF (LEN_TRIM(let3)== 0) THEN ! No third character cluster indicates this is a whole-rod channel or endpoint + IF (let2(1:2) == 'NA') THEN + PRINT *, 'Node A' + p%OutParam(I)%NodeID = 0 + let2 = let2(3:) + ELSE IF (let2(1:2) == 'NB') THEN + PRINT *, 'Node B' + p%OutParam(I)%NodeID = m%RodList(p%OutParam(I)%ObjID)%N + PRINT *, 'Node B ID:', p%OutParam(I)%NodeID + let2 = let2(3:) + ELSE + p%OutParam(I)%NodeID = -1 + END IF qVal = let2 ! quantity type string ELSE IF (num2/=" ") THEN READ (num2,*) nID ! rod node ID @@ -561,16 +599,6 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) CYCLE END IF - ! object number - IF (num1/=" ") THEN - READ (num1,*) oID - p%OutParam(I)%ObjID = oID ! line or connect ID number - ELSE - CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid - CALL WrScr('Warning: invalid output specifier '//trim(OutListTmp)//'. Object ID missing.') - CYCLE - END IF - ! which kind of quantity? IF (qVal == 'PX') THEN p%OutParam(I)%QType = PosX @@ -581,6 +609,15 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) ELSE IF (qVal == 'PZ') THEN p%OutParam(I)%QType = PosZ p%OutParam(I)%Units = UnitList(PosZ) + ELSE IF (qVal == 'RX') THEN + p%OutParam(I)%QType = RotX + p%OutParam(I)%Units = UnitList(RotX) + ELSE IF (qVal == 'RY') THEN + p%OutParam(I)%QType = RotY + p%OutParam(I)%Units = UnitList(RotY) + ELSE IF (qVal == 'RZ') THEN + p%OutParam(I)%QType = RotZ + p%OutParam(I)%Units = UnitList(RotZ) ELSE IF (qVal == 'VX') THEN p%OutParam(I)%QType = VelX p%OutParam(I)%Units = UnitList(VelX) @@ -590,6 +627,15 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) ELSE IF (qVal == 'VZ') THEN p%OutParam(I)%QType = VelZ p%OutParam(I)%Units = UnitList(VelZ) + ELSE IF (qVal == 'RVX') THEN + p%OutParam(I)%QType = RVelX + p%OutParam(I)%Units = UnitList(RVelX) + ELSE IF (qVal == 'RVY') THEN + p%OutParam(I)%QType = RVelY + p%OutParam(I)%Units = UnitList(RVelY) + ELSE IF (qVal == 'RVZ') THEN + p%OutParam(I)%QType = RVelZ + p%OutParam(I)%Units = UnitList(RVelZ) ELSE IF (qVal == 'AX') THEN p%OutParam(I)%QType = AccX p%OutParam(I)%Units = UnitList(AccX) @@ -599,9 +645,24 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) ELSE IF (qVal == 'AZ') THEN p%OutParam(I)%QType = AccZ p%OutParam(I)%Units = UnitList(AccZ) - ELSE IF ((qVal == 'T') .or. (qVal == 'TEN')) THEN + ELSE IF (qVal == 'RAX') THEN + p%OutParam(I)%QType = RAccX + p%OutParam(I)%Units = UnitList(RAccX) + ELSE IF (qVal == 'RAY') THEN ! fixed typo Nov 24 + p%OutParam(I)%QType = RAccY + p%OutParam(I)%Units = UnitList(RAccY) + ELSE IF (qVal == 'RAZ') THEN + p%OutParam(I)%QType = RAccZ + p%OutParam(I)%Units = UnitList(RAccZ) + ELSE IF ((qVal == 'T') .OR. (qVal == 'TEN')) THEN p%OutParam(I)%QType = Ten p%OutParam(I)%Units = UnitList(Ten) + ELSE IF ((qVal == 'TA') .OR. (qVal == 'TENA')) THEN + p%OutParam(I)%QType = TenA + p%OutParam(I)%Units = UnitList(Ten) + ELSE IF ((qVal == 'TB') .OR. (qVal == 'TENB')) THEN + p%OutParam(I)%QType = TenB + p%OutParam(I)%Units = UnitList(Ten) ELSE IF (qVal == 'FX') THEN p%OutParam(I)%QType = FX p%OutParam(I)%Units = UnitList(FX) @@ -611,15 +672,15 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) ELSE IF (qVal == 'FZ') THEN p%OutParam(I)%QType = FZ p%OutParam(I)%Units = UnitList(FZ) ! <<<< should add moments as well <<<< - ELSE IF (qVal == 'ROLL') THEN - p%OutParam(I)%QType = Roll - p%OutParam(I)%Units = UnitList(Roll) - ELSE IF (qVal == 'PITCH') THEN - p%OutParam(I)%QType = Pitch - p%OutParam(I)%Units = UnitList(Pitch) - ELSE IF (qVal == 'YAW') THEN - p%OutParam(I)%QType = Yaw - p%OutParam(I)%Units = UnitList(Yaw) + ELSE IF (qVal == 'MX') THEN + p%OutParam(I)%QType = MX + p%OutParam(I)%Units = UnitList(MX) + ELSE IF (qVal == 'MY') THEN + p%OutParam(I)%QType = MY + p%OutParam(I)%Units = UnitList(MY) + ELSE IF (qVal == 'MZ') THEN + p%OutParam(I)%QType = MZ + p%OutParam(I)%Units = UnitList(MZ) ! <<<< should add moments as well <<<< ELSE IF (qVal == 'SUB') THEN p%OutParam(I)%QType = Sub p%OutParam(I)%Units = UnitList(Sub) @@ -646,9 +707,9 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid END IF - ELSE IF (p%OutParam(I)%OType==2) THEN ! Connect - IF (p%OutParam(I)%ObjID > p%NConnects) THEN - CALL WrScr('Warning: output Connect index excedes number of Connects in requested output '//trim(OutListTmp)//'.') + ELSE IF (p%OutParam(I)%OType==2) THEN ! point + IF (p%OutParam(I)%ObjID > p%NPoints) THEN + CALL WrScr('Warning: output point index excedes number of points in requested output '//trim(OutListTmp)//'.') CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid END IF @@ -660,8 +721,8 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) IF (p%OutParam(I)%NodeID > m%RodList(p%OutParam(I)%ObjID)%N) THEN CALL WrScr('Warning: output node index excedes number of nodes in requested output '//trim(OutListTmp)//'.') CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid - ELSE IF (p%OutParam(I)%NodeID < 0) THEN - CALL WrScr('Warning: output node index is less than zero in requested output '//trim(OutListTmp)//'.') + ELSE IF (p%OutParam(I)%NodeID < -1) THEN + CALL WrScr('Warning: output node index is less than -1 in requested output '//trim(OutListTmp)//'.') CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid END IF @@ -1287,87 +1348,142 @@ SUBROUTINE MDIO_WriteOutputs( Time, p, m, y, ErrStat, ErrMsg ) y%WriteOutput(I) = m%LineList(p%OutParam(I)%ObjID)%rd(2,p%OutParam(I)%NodeID) ! y velocity CASE (VelZ) y%WriteOutput(I) = m%LineList(p%OutParam(I)%ObjID)%rd(3,p%OutParam(I)%NodeID) ! z velocity + CASE (FX) + y%WriteOutput(I) = m%LineList(p%OutParam(I)%ObjID)%Fnet(1,p%OutParam(I)%NodeID) ! node force in x + CASE (FY) + y%WriteOutput(I) = m%LineList(p%OutParam(I)%ObjID)%Fnet(2,p%OutParam(I)%NodeID) ! node force in y + CASE (FZ) + y%WriteOutput(I) = m%LineList(p%OutParam(I)%ObjID)%Fnet(3,p%OutParam(I)%NodeID) ! node force in z CASE (Ten) y%WriteOutput(I) = Line_GetNodeTen(m%LineList(p%OutParam(I)%ObjID), p%OutParam(I)%NodeID, p) ! this is actually the segment tension ( 1 < NodeID < N ) Should deal with properly! - + CASE (TenA) + y%WriteOutput(I) = Line_GetNodeTen(m%LineList(p%OutParam(I)%ObjID), 0, p) + CASE (TenB) + y%WriteOutput(I) = Line_GetNodeTen(m%LineList(p%OutParam(I)%ObjID), m%LineList(p%OutParam(I)%ObjID)%N, p) CASE DEFAULT y%WriteOutput(I) = 0.0_ReKi ErrStat = ErrID_Warn ErrMsg = ' Unsupported output quantity '//TRIM(p%OutParam(I)%Name)//' requested from Line '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' END SELECT - ELSE IF (p%OutParam(I)%OType == 2) THEN ! if dealing with a Connect output + ELSE IF (p%OutParam(I)%OType == 2) THEN ! if dealing with a Point output SELECT CASE (p%OutParam(I)%QType) CASE (PosX) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%r(1) ! x position + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%r(1) ! x position CASE (PosY) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%r(2) ! y position + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%r(2) ! y position CASE (PosZ) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%r(3) ! z position + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%r(3) ! z position CASE (VelX) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%rd(1) ! x velocity + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%rd(1) ! x velocity CASE (VelY) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%rd(2) ! y velocity + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%rd(2) ! y velocity CASE (VelZ) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%rd(3) ! z velocity + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%rd(3) ! z velocity CASE (AccX) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%a(1) ! x acceleration + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%a(1) ! x acceleration CASE (AccY) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%a(2) ! y acceleration + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%a(2) ! y acceleration CASE (AccZ) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%a(3) ! z acceleration + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%a(3) ! z acceleration CASE (Ten) - y%WriteOutput(I) = TwoNorm(m%ConnectList(p%OutParam(I)%ObjID)%Fnet) ! total force magnitude on a connect (used eg. for fairlead and anchor tensions) + y%WriteOutput(I) = sqrt(m%PointList(p%OutParam(I)%ObjID)%Fnet(1)**2 + m%PointList(p%OutParam(I)%ObjID)%Fnet(2)**2 + m%PointList(p%OutParam(I)%ObjID)%Fnet(3)**2) ! total force magnitude on a point (used eg. for fairlead and anchor tensions) CASE (FX) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%Fnet(1) ! total force in x - added Nov 24 + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%Fnet(1) ! total force in x - added Nov 24 CASE (FY) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%Fnet(2) ! total force in y + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%Fnet(2) ! total force in y CASE (FZ) - y%WriteOutput(I) = m%ConnectList(p%OutParam(I)%ObjID)%Fnet(3) ! total force in z + y%WriteOutput(I) = m%PointList(p%OutParam(I)%ObjID)%Fnet(3) ! total force in z CASE DEFAULT y%WriteOutput(I) = 0.0_ReKi ErrStat = ErrID_Warn - ErrMsg = ' Unsupported output quantity '//TRIM(p%OutParam(I)%Name)//' requested from Connection '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' + ErrMsg = ' Unsupported output quantity '//TRIM(p%OutParam(I)%Name)//' requested from Point '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' END SELECT ELSE IF (p%OutParam(I)%OType == 3) THEN ! if dealing with a Rod output - SELECT CASE (p%OutParam(I)%QType) - CASE (PosX) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(1,p%OutParam(I)%NodeID) ! x position - CASE (PosY) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(2,p%OutParam(I)%NodeID) ! y position - CASE (PosZ) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(3,p%OutParam(I)%NodeID) ! z position - CASE (VelX) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(1,p%OutParam(I)%NodeID) ! x velocity - CASE (VelY) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(2,p%OutParam(I)%NodeID) ! y velocity - CASE (VelZ) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(3,p%OutParam(I)%NodeID) ! z velocity - CASE (AccX) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(1) ! x acceleration <<< should this become distributed for each node? - CASE (AccY) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(2) ! y acceleration - CASE (AccZ) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(3) ! z acceleration - CASE (FX) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(1) ! total force in x - added Nov 24 - CASE (FY) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(2) ! total force in y - CASE (FZ) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(3) ! total force in z - CASE (Roll) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%roll*180.0/pi ! rod roll - CASE (Pitch) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%pitch*180.0/pi ! rod pitch - CASE (Sub) - y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%h0 / m%RodList(p%OutParam(I)%ObjID)%UnstrLen ! rod submergence - CASE DEFAULT - y%WriteOutput(I) = 0.0_ReKi - ErrStat = ErrID_Warn - ErrMsg = ' Unsupported output quantity '//TRIM(p%OutParam(I)%Name)//' requested from Rod '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' - END SELECT + IF (p%OutParam(I)%NodeID == -1) THEN ! if whole rod outputs or node 0 (aka end A) + SELECT CASE (p%OutParam(I)%QType) + CASE (PosX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r6(1) ! x position + CASE (PosY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r6(2) ! y position + CASE (PosZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r6(3) ! z position + CASE (RotX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%roll*180.0/pi ! rod roll + CASE (RotY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%pitch*180.0/pi ! rod pitch + CASE (VelX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%v6(1) ! x velocity + CASE (VelY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%v6(2) ! y velocity + CASE (VelZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%v6(3) ! z velocity + CASE (RVelX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%v6(4)*180.0/pi ! rx velocity + CASE (RVelY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%v6(5)*180.0/pi ! ry velocity + CASE (AccX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(1) ! x acceleration <<< should this become distributed for each node? + CASE (AccY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(2) ! y acceleration + CASE (AccZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(3) ! z acceleration + CASE (RAccX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(4)*180.0/pi ! rx acceleration <<< should this become distributed for each node? + CASE (RAccY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%a6(5)*180.0/pi ! ry acceleration + CASE (FX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(1) ! total force in x - added Nov 24 + CASE (FY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(2) ! total force in y + CASE (FZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(3) ! total force in z + CASE (MX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(4) ! total force in x - added Nov 24 + CASE (MY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(5) ! total force in y + CASE (MZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%F6net(6) ! total force in z + CASE (Sub) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%h0 / m%RodList(p%OutParam(I)%ObjID)%UnstrLen ! rod submergence + CASE (TenA) + y%WriteOutput(I) = sqrt(m%RodList(p%OutParam(I)%ObjID)%FextA(1)**2 + m%RodList(p%OutParam(I)%ObjID)%FextA(2)**2 + m%RodList(p%OutParam(I)%ObjID)%FextA(3)**2)! external forces on end A + CASE (TenB) + y%WriteOutput(I) = sqrt(m%RodList(p%OutParam(I)%ObjID)%FextB(1)**2 + m%RodList(p%OutParam(I)%ObjID)%FextB(2)**2 + m%RodList(p%OutParam(I)%ObjID)%FextB(3)**2) ! external forces on end B + CASE DEFAULT + y%WriteOutput(I) = 0.0_ReKi + ErrStat = ErrID_Warn + ErrMsg = ' Unsupported output quantity for whole rod'//TRIM(p%OutParam(I)%Name)//' requested from Rod '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' + END SELECT + + ELSE ! if rod node outputs + SELECT CASE (p%OutParam(I)%QType) + CASE (PosX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(1,p%OutParam(I)%NodeID) ! x position + CASE (PosY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(2,p%OutParam(I)%NodeID) ! y position + CASE (PosZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%r(3,p%OutParam(I)%NodeID) ! z position + CASE (VelX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(1,p%OutParam(I)%NodeID) ! x velocity + CASE (VelY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(2,p%OutParam(I)%NodeID) ! y velocity + CASE (VelZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%rd(3,p%OutParam(I)%NodeID) ! z velocity + CASE (FX) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%Fnet(1,p%OutParam(I)%NodeID) ! node force in x + CASE (FY) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%Fnet(2,p%OutParam(I)%NodeID) ! node force in y + CASE (FZ) + y%WriteOutput(I) = m%RodList(p%OutParam(I)%ObjID)%Fnet(3,p%OutParam(I)%NodeID) ! node force in z + CASE DEFAULT + y%WriteOutput(I) = 0.0_ReKi + ErrStat = ErrID_Warn + ErrMsg = ' Unsupported output quantity for rod nodes '//TRIM(p%OutParam(I)%Name)//' requested from Rod '//TRIM(Num2Lstr(p%OutParam(I)%ObjID))//'.' + END SELECT + END IF ELSE IF (p%OutParam(I)%OType == 4) THEN ! if dealing with a Body output SELECT CASE (p%OutParam(I)%QType) @@ -1377,24 +1493,50 @@ SUBROUTINE MDIO_WriteOutputs( Time, p, m, y, ErrStat, ErrMsg ) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(2) ! y position CASE (PosZ) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(3) ! z position + CASE (RotX) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(4)*180.0/pi ! roll + CASE (RotY) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(5)*180.0/pi ! pitch + CASE (RotZ) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(6)*180.0/pi ! yaw CASE (VelX) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(1) ! x velocity CASE (VelY) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(2) ! y velocity CASE (VelZ) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(3) ! z velocity + CASE (RVelX) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(4)*180.0/pi ! rx velocity + CASE (RVelY) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(5)*180.0/pi ! ry velocity + CASE (RVelZ) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%v6(6)*180.0/pi ! rz velocity + CASE (AccX) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(1) ! x acceleration + CASE (AccY) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(2) ! y acceleration + CASE (AccZ) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(3) ! z acceleration + CASE (RAccX) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(4)*180.0/pi ! rx acceleration + CASE (RAccY) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(5)*180.0/pi ! ry acceleration + CASE (RAccZ) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%a6(6)*180.0/pi ! rz acceleration CASE (FX) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(1) ! total force in x - added Nov 24 CASE (FY) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(2) ! total force in y CASE (FZ) y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(3) ! total force in z - CASE (Roll) - y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(4)*180.0/pi ! roll - CASE (Pitch) - y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(5)*180.0/pi ! pitch - CASE (Yaw) - y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%r6(6)*180.0/pi ! yaw + CASE (TEN) + y%WriteOutput(I) = sqrt(m%BodyList(p%OutParam(I)%ObjID)%F6net(1)**2 + m%BodyList(p%OutParam(I)%ObjID)%F6net(2)**2 + m%BodyList(p%OutParam(I)%ObjID)%F6net(3)**2) + CASE (MX) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(4) ! total moment in x - added Nov 24 + CASE (MY) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(5) ! total moment in y + CASE (MZ) + y%WriteOutput(I) = m%BodyList(p%OutParam(I)%ObjID)%F6net(6) ! total moment in z CASE DEFAULT y%WriteOutput(I) = 0.0_ReKi ErrStat = ErrID_Warn diff --git a/modules/moordyn/src/MoorDyn_Line.f90 b/modules/moordyn/src/MoorDyn_Line.f90 index 1d6b216424..ee381bc988 100644 --- a/modules/moordyn/src/MoorDyn_Line.f90 +++ b/modules/moordyn/src/MoorDyn_Line.f90 @@ -1005,10 +1005,10 @@ SUBROUTINE Line_GetStateDeriv(Line, Xd, m, p) !, FairFtot, FairMtot, AnchFtot, ! Real(DbKi), INTENT (IN) :: t ! instantaneous time ! TYPE(MD_Line), INTENT (INOUT) :: Line ! label for the current line, for convenience ! TYPE(MD_LineProp), INTENT(IN) :: LineProp ! the single line property set for the line of interest - ! Real(DbKi), INTENT(INOUT) :: FairFtot(:) ! total force on Connect top of line is attached to - ! Real(DbKi), INTENT(INOUT) :: FairMtot(:,:) ! total mass of Connect top of line is attached to - ! Real(DbKi), INTENT(INOUT) :: AnchFtot(:) ! total force on Connect bottom of line is attached to - ! Real(DbKi), INTENT(INOUT) :: AnchMtot(:,:) ! total mass of Connect bottom of line is attached to + ! Real(DbKi), INTENT(INOUT) :: FairFtot(:) ! total force on Point top of line is attached to + ! Real(DbKi), INTENT(INOUT) :: FairMtot(:,:) ! total mass of Point top of line is attached to + ! Real(DbKi), INTENT(INOUT) :: AnchFtot(:) ! total force on Point bottom of line is attached to + ! Real(DbKi), INTENT(INOUT) :: AnchMtot(:,:) ! total mass of Point bottom of line is attached to INTEGER(IntKi) :: i ! index of segments or nodes along line @@ -1070,10 +1070,10 @@ SUBROUTINE Line_GetStateDeriv(Line, Xd, m, p) !, FairFtot, FairMtot, AnchFtot, ! ! set end node positions and velocities from connect objects' states ! DO J = 1, 3 - ! Line%r( J,N) = m%ConnectList(Line%FairConnect)%r(J) - ! Line%r( J,0) = m%ConnectList(Line%AnchConnect)%r(J) - ! Line%rd(J,N) = m%ConnectList(Line%FairConnect)%rd(J) - ! Line%rd(J,0) = m%ConnectList(Line%AnchConnect)%rd(J) + ! Line%r( J,N) = m%PointList(Line%FairPoint)%r(J) + ! Line%r( J,0) = m%PointList(Line%AnchPoint)%r(J) + ! Line%rd(J,N) = m%PointList(Line%FairPoint)%rd(J) + ! Line%rd(J,0) = m%PointList(Line%AnchPoint)%rd(J) ! END DO @@ -1225,10 +1225,10 @@ SUBROUTINE Line_GetStateDeriv(Line, Xd, m, p) !, FairFtot, FairMtot, AnchFtot, ! loop through all nodes to calculate bending forces due to bending stiffness do i=0,N - ! end node A case (only if attached to a Rod, i.e. a cantilever rather than pinned connection) + ! end node A case (only if attached to a Rod, i.e. a cantilever rather than pinned point) if (i==0) then - if (Line%endTypeA > 0) then ! if attached to Rod i.e. cantilever connection + if (Line%endTypeA > 0) then ! if attached to Rod i.e. cantilever point Kurvi = GetCurvature(Line%lstr(1), Line%q(:,0), Line%qs(:,1)) ! curvature (assuming rod angle is node angle which is middle of if there was a segment -1/2) @@ -1248,10 +1248,10 @@ SUBROUTINE Line_GetStateDeriv(Line, Xd, m, p) !, FairFtot, FairMtot, AnchFtot, end if - ! end node A case (only if attached to a Rod, i.e. a cantilever rather than pinned connection) + ! end node A case (only if attached to a Rod, i.e. a cantilever rather than pinned point) else if (i==N) then - if (Line%endTypeB > 0) then ! if attached to Rod i.e. cantilever connection + if (Line%endTypeB > 0) then ! if attached to Rod i.e. cantilever point Kurvi = GetCurvature(Line%lstr(N), Line%qs(:,N), Line%q(:,N)) ! curvature (assuming rod angle is node angle which is middle of if there was a segment -1/2 @@ -1488,7 +1488,7 @@ SUBROUTINE Line_GetStateDeriv(Line, Xd, m, p) !, FairFtot, FairMtot, AnchFtot, END DO - ! ! add force and mass of end nodes to the Connects they correspond to <<<<<<<<<<<< do this from Connection instead now! + ! ! add force and mass of end nodes to the Points they correspond to <<<<<<<<<<<< do this from Point instead now! ! DO J = 1,3 ! FairFtot(J) = FairFtot(J) + Line%F(J,N) ! AnchFtot(J) = AnchFtot(J) + Line%F(J,0) @@ -1516,10 +1516,10 @@ SUBROUTINE Line_SetEndKinematics(Line, r_in, rd_in, t, topOfLine) IF (topOfLine==1) THEN inode = Line%N - Line%endTypeB = 0 ! set as ball rather than rigid connection (unless changed later by SetEndOrientation) + Line%endTypeB = 0 ! set as ball rather than rigid point (unless changed later by SetEndOrientation) ELSE inode = 0 - Line%endTypeA = 0 ! set as ball rather than rigid connection (unless changed later by SetEndOrientation) + Line%endTypeA = 0 ! set as ball rather than rigid point (unless changed later by SetEndOrientation) END IF !Line%r( :,inode) = r_in diff --git a/modules/moordyn/src/MoorDyn_Misc.f90 b/modules/moordyn/src/MoorDyn_Misc.f90 index 90cb049d18..3f52dfc16e 100644 --- a/modules/moordyn/src/MoorDyn_Misc.f90 +++ b/modules/moordyn/src/MoorDyn_Misc.f90 @@ -1005,7 +1005,7 @@ SUBROUTINE CopyWaterKinFromHydroDyn(p, InitInp) ! J = J + (m%RodList(l)%N + 1) ! END DO ! ! Point reference point coordinates - ! J = J + p%nConnects + ! J = J + p%nPoints ! ! Line internal node coordinates ! DO l = 1, p%nLines ! J = J + (m%LineList(l)%N - 1) @@ -1035,9 +1035,9 @@ SUBROUTINE CopyWaterKinFromHydroDyn(p, InitInp) ! END DO ! END DO ! ! Point reference point coordinates - ! DO I = 1, p%nConnects + ! DO I = 1, p%nPoints ! J = J + 1 - ! y%rAll(:,J) = m%ConnectList(I)%r + ! y%rAll(:,J) = m%PointList(I)%r ! END DO ! ! Line internal node coordinates ! DO I = 1, p%nLines diff --git a/modules/moordyn/src/MoorDyn_Point.f90 b/modules/moordyn/src/MoorDyn_Point.f90 index fce8aab12f..771b3a0cbf 100644 --- a/modules/moordyn/src/MoorDyn_Point.f90 +++ b/modules/moordyn/src/MoorDyn_Point.f90 @@ -32,61 +32,61 @@ MODULE MoorDyn_Point INTEGER(IntKi), PARAMETER :: wordy = 0 ! verbosity level. >1 = more console output - PUBLIC :: Connect_Initialize - PUBLIC :: Connect_SetKinematics - PUBLIC :: Connect_SetState - PUBLIC :: Connect_GetStateDeriv - PUBLIC :: Connect_DoRHS - PUBLIC :: Connect_GetCoupledForce - PUBLIC :: Connect_GetNetForceAndMass - PUBLIC :: Connect_AddLine - PUBLIC :: Connect_RemoveLine + PUBLIC :: Point_Initialize + PUBLIC :: Point_SetKinematics + PUBLIC :: Point_SetState + PUBLIC :: Point_GetStateDeriv + PUBLIC :: Point_DoRHS + PUBLIC :: Point_GetCoupledForce + PUBLIC :: Point_GetNetForceAndMass + PUBLIC :: Point_AddLine + PUBLIC :: Point_RemoveLine CONTAINS !-------------------------------------------------------------- - SUBROUTINE Connect_Initialize(Connect, states, m) + SUBROUTINE Point_Initialize(Point, states, m) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connection object - Real(DbKi), INTENT(INOUT) :: states(6) ! state vector section for this Connection + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object + Real(DbKi), INTENT(INOUT) :: states(6) ! state vector section for this Point TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects INTEGER(IntKi) :: l - if (Connect%typeNum == 0) then ! error check + if (Point%typeNum == 0) then ! error check ! pass kinematics to any attached lines so they have initial positions at this initialization stage - DO l=1,Connect%nAttached - IF (wordy > 1) print *, "Connect ", Connect%IdNum, " setting end kinematics of line ", Connect%attached(l), " to ", Connect%r - CALL Line_SetEndKinematics(m%LineList(Connect%attached(l)), Connect%r, Connect%rd, 0.0_DbKi, Connect%Top(l)) + DO l=1,Point%nAttached + IF (wordy > 1) print *, "Point ", Point%IdNum, " setting end kinematics of line ", Point%attached(l), " to ", Point%r + CALL Line_SetEndKinematics(m%LineList(Point%attached(l)), Point%r, Point%rd, 0.0_DbKi, Point%Top(l)) END DO ! assign initial node kinematics to state vector - states(4:6) = Connect%r - states(1:3) = Connect%rd + states(4:6) = Point%r + states(1:3) = Point%rd - IF (wordy > 0) print *, "Initialized Connection ", Connect%IdNum + IF (wordy > 0) print *, "Initialized Point ", Point%IdNum else - CALL WrScr(" Error: wrong Point type given to Connect_Initialize for number "//trim(Int2Lstr(Connect%idNum))) + CALL WrScr(" Error: wrong Point type given to Point_Initialize for number "//trim(Int2Lstr(Point%idNum))) end if - END SUBROUTINE Connect_Initialize + END SUBROUTINE Point_Initialize !-------------------------------------------------------------- !-------------------------------------------------------------- - SUBROUTINE Connect_SetKinematics(Connect, r_in, rd_in, a_in, t, m) + SUBROUTINE Point_SetKinematics(Point, r_in, rd_in, a_in, t, m) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object Real(DbKi), INTENT(IN ) :: r_in( 3) ! position Real(DbKi), INTENT(IN ) :: rd_in(3) ! velocity - Real(DbKi), INTENT(IN ) :: a_in(3) ! acceleration (only used for coupled connects) + Real(DbKi), INTENT(IN ) :: a_in(3) ! acceleration (only used for coupled points) Real(DbKi), INTENT(IN ) :: t ! instantaneous time TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects @@ -94,35 +94,35 @@ SUBROUTINE Connect_SetKinematics(Connect, r_in, rd_in, a_in, t, m) INTEGER(IntKi) :: l ! store current time - Connect%time = t + Point%time = t - ! if (Connect%typeNum==0) THEN ! anchor ( <<< to be changed/expanded) ... in MoorDyn F also used for coupled connections + ! if (Point%typeNum==0) THEN ! anchor ( <<< to be changed/expanded) ... in MoorDyn F also used for coupled points ! set position and velocity - Connect%r = r_in - Connect%rd = rd_in - Connect%a = a_in + Point%r = r_in + Point%rd = rd_in + Point%a = a_in ! pass latest kinematics to any attached lines - DO l=1,Connect%nAttached - CALL Line_SetEndKinematics(m%LineList(Connect%attached(l)), Connect%r, Connect%rd, t, Connect%Top(l)) + DO l=1,Point%nAttached + CALL Line_SetEndKinematics(m%LineList(Point%attached(l)), Point%r, Point%rd, t, Point%Top(l)) END DO ! else ! - ! PRINT*,"Error: setKinematics called for wrong Connection type. Connection ", Connect%IdNum, " type ", Connect%typeNum + ! PRINT*,"Error: setKinematics called for wrong Point type. Point ", Point%IdNum, " type ", Point%typeNum ! END IF - END SUBROUTINE Connect_SetKinematics + END SUBROUTINE Point_SetKinematics !-------------------------------------------------------------- !-------------------------------------------------------------- - SUBROUTINE Connect_SetState(Connect, X, t, m) + SUBROUTINE Point_SetState(Point, X, t, m) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object Real(DbKi), INTENT(IN ) :: X(:) ! state vector section for this line Real(DbKi), INTENT(IN ) :: t ! instantaneous time TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects @@ -132,26 +132,26 @@ SUBROUTINE Connect_SetState(Connect, X, t, m) ! store current time - Connect%time = t + Point%time = t ! from state values, get r and rdot values DO J=1,3 - Connect%r( J) = X(3 + J) ! get positions - Connect%rd(J) = X( J) ! get velocities + Point%r( J) = X(3 + J) ! get positions + Point%rd(J) = X( J) ! get velocities END DO ! pass latest kinematics to any attached lines - DO l=1,Connect%nAttached - CALL Line_SetEndKinematics(m%LineList(Connect%attached(l)), Connect%r, Connect%rd, t, Connect%Top(l)) + DO l=1,Point%nAttached + CALL Line_SetEndKinematics(m%LineList(Point%attached(l)), Point%r, Point%rd, t, Point%Top(l)) END DO - END SUBROUTINE Connect_SetState + END SUBROUTINE Point_SetState !-------------------------------------------------------------- !-------------------------------------------------------------- - SUBROUTINE Connect_GetStateDeriv(Connect, Xd, m, p) + SUBROUTINE Point_GetStateDeriv(Point, Xd, m, p) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object Real(DbKi), INTENT(INOUT) :: Xd(:) ! state derivative vector section for this line TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects @@ -167,7 +167,7 @@ SUBROUTINE Connect_GetStateDeriv(Connect, Xd, m, p) Real(DbKi) :: S(3,3) ! inverse mass matrix - CALL Connect_DoRHS(Connect, m, p) + CALL Point_DoRHS(Point, m, p) ! // solve for accelerations in [M]{a}={f} using LU decomposition ! double M_tot[9]; // serialize total mass matrix for easy processing @@ -182,33 +182,33 @@ SUBROUTINE Connect_GetStateDeriv(Connect, Xd, m, p) ! invert node mass matrix - CALL Inverse3by3(S, Connect%M) + CALL Inverse3by3(S, Point%M) ! accelerations - Connect%a = MATMUL(S, Connect%Fnet) + Point%a = MATMUL(S, Point%Fnet) ! fill in state derivatives - Xd(4:6) = Connect%rd ! dxdt = V (velocities) - Xd(1:3) = Connect%a ! dVdt = RHS * A (accelerations) + Xd(4:6) = Point%rd ! dxdt = V (velocities) + Xd(1:3) = Point%a ! dVdt = RHS * A (accelerations) ! check for NaNs DO J = 1, 6 IF (Is_NaN(Xd(J))) THEN - CALL WrScr("NaN detected at time "//trim(Num2LStr(Connect%time))//" in Point "//trim(Int2LStr(Connect%IdNum))//" in MoorDyn.") + CALL WrScr("NaN detected at time "//trim(Num2LStr(Point%time))//" in Point "//trim(Int2LStr(Point%IdNum))//" in MoorDyn.") IF (wordy > 1) print *, "state derivatives:" IF (wordy > 1) print *, Xd EXIT END IF END DO - END SUBROUTINE Connect_GetStateDeriv + END SUBROUTINE Point_GetStateDeriv !-------------------------------------------------------------- !-------------------------------------------------------------- - SUBROUTINE Connect_DoRHS(Connect, m, p) + SUBROUTINE Point_DoRHS(Point, m, p) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects TYPE(MD_ParameterType),INTENT(IN ) :: p ! Parameters @@ -224,47 +224,47 @@ SUBROUTINE Connect_DoRHS(Connect, m, p) Real(DbKi) :: M_i(3,3) ! mass from an attached line - ! start with the Connection's own forces including buoyancy and weight, and its own mass - Connect%Fnet(1) = Connect%conFX - Connect%Fnet(2) = Connect%conFY - Connect%Fnet(3) = Connect%conFZ + Connect%conV*p%rhoW*p%g - Connect%conM*p%g + ! start with the Point's own forces including buoyancy and weight, and its own mass + Point%Fnet(1) = Point%pointFX + Point%Fnet(2) = Point%pointFY + Point%Fnet(3) = Point%pointFZ + Point%pointV*p%rhoW*p%g - Point%pointM*p%g - Connect%M = 0.0_DbKi ! clear (zero) the connect mass matrix + Point%M = 0.0_DbKi ! clear (zero) the point mass matrix DO J = 1,3 - Connect%M (J,J) = Connect%conM ! set the diagonals to the self-mass (to start with) + Point%M (J,J) = Point%pointM ! set the diagonals to the self-mass (to start with) END DO - ! print *, "connection number", Connect%IdNum - ! print *, "attached lines: ", Connect%attached + ! print *, "point number", Point%IdNum + ! print *, "attached lines: ", Point%attached ! print *, "size of line list" , size(m%LineList) ! loop through attached lines, adding force and mass contributions - DO l=1,Connect%nAttached + DO l=1,Point%nAttached ! print *, " l", l - ! print *, Connect%attached(l) - ! print *, m%LineList(Connect%attached(l))%Fnet + ! print *, Point%attached(l) + ! print *, m%LineList(Point%attached(l))%Fnet ! ! - ! print *, " attached line ID", m%LineList(Connect%attached(l))%IdNum + ! print *, " attached line ID", m%LineList(Point%attached(l))%IdNum - CALL Line_GetEndStuff(m%LineList(Connect%attached(l)), Fnet_i, Moment_dummy, M_i, Connect%Top(l)) + CALL Line_GetEndStuff(m%LineList(Point%attached(l)), Fnet_i, Moment_dummy, M_i, Point%Top(l)) ! sum quantitites - Connect%Fnet = Connect%Fnet + Fnet_i - Connect%M = Connect%M + M_i + Point%Fnet = Point%Fnet + Fnet_i + Point%M = Point%M + M_i END DO ! XXXWhen this sub is called, any self weight, buoyancy, or external forcing should have already been - ! added by the calling subroutine. The only thing left is any added mass or drag forces from the connection (e.g. float) + ! added by the calling subroutine. The only thing left is any added mass or drag forces from the point (e.g. float) ! itself, which will be added below.XXX - ! IF (EqualRealNos(t, 0.0_DbKi)) THEN ! this is old: with current IC gen approach, we skip the first call to the line objects, because they're set AFTER the call to the connects + ! IF (EqualRealNos(t, 0.0_DbKi)) THEN ! this is old: with current IC gen approach, we skip the first call to the line objects, because they're set AFTER the call to the points ! ! DO J = 1,3 ! Xd(3+J) = X(J) ! velocities - these are unused in integration @@ -273,106 +273,106 @@ SUBROUTINE Connect_DoRHS(Connect, m, p) ! ELSE ! ! from state values, get r and rdot values ! DO J = 1,3 - ! Connect%r(J) = X(3 + J) ! get positions - ! Connect%rd(J) = X(J) ! get velocities + ! Point%r(J) = X(3 + J) ! get positions + ! Point%rd(J) = X(J) ! get velocities ! END DO ! END IF - ! add any added mass and drag forces from the Connect body itself + ! add any added mass and drag forces from the Point body itself DO J = 1,3 - Connect%Fnet(J) = Connect%Fnet(J) - 0.5 * p%rhoW * Connect%rd(J) * abs(Connect%rd(J)) * Connect%conCdA; ! add drag forces - corrected Nov 24 - Connect%M (J,J) = Connect%M (J,J) + Connect%conV*p%rhoW*Connect%conCa; ! add added mass + Point%Fnet(J) = Point%Fnet(J) - 0.5 * p%rhoW * Point%rd(J) * abs(Point%rd(J)) * Point%pointCdA; ! add drag forces - corrected Nov 24 + Point%M (J,J) = Point%M (J,J) + Point%pointV*p%rhoW*Point%pointCa; ! add added mass END DO - ! would this sub ever need to include the m*a inertial term? Is it ever called for coupled connects? <<< + ! would this sub ever need to include the m*a inertial term? Is it ever called for coupled points? <<< - END SUBROUTINE Connect_DoRHS + END SUBROUTINE Point_DoRHS !===================================================================== - ! calculate the force including inertial loads on connect that is coupled + ! calculate the force including inertial loads on point that is coupled !-------------------------------------------------------------- - SUBROUTINE Connect_GetCoupledForce(Connect, Fnet_out, m, p) + SUBROUTINE Point_GetCoupledForce(Point, Fnet_out, m, p) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connect object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object Real(DbKi), INTENT( OUT) :: Fnet_out(3) ! force and moment vector about rRef TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects TYPE(MD_ParameterType),INTENT(IN ) :: p ! Parameters Real(DbKi) :: F_iner(3) ! inertial force - IF (Connect%typeNum == -1) then - ! calculate forces and masses of connect - CALL Connect_DoRHS(Connect, m, p) + IF (Point%typeNum == -1) then + ! calculate forces and masses of point + CALL Point_DoRHS(Point, m, p) ! add inertial loads as appropriate - F_iner = -MATMUL(Connect%M, Connect%a) ! inertial loads - Fnet_out = Connect%Fnet + F_iner ! add inertial loads + F_iner = -MATMUL(Point%M, Point%a) ! inertial loads + Fnet_out = Point%Fnet + F_iner ! add inertial loads ELSE - CALL WrScr("Connect_GetCoupledForce called for wrong (uncoupled) Point type in MoorDyn!") + CALL WrScr("Point_GetCoupledForce called for wrong (uncoupled) Point type in MoorDyn!") END IF - END SUBROUTINE Connect_GetCoupledForce + END SUBROUTINE Point_GetCoupledForce - ! calculate the force and mass contributions of the connect on the parent body (only for type 3 connects?) + ! calculate the force and mass contributions of the point on the parent body (only for type 3 points?) !-------------------------------------------------------------- - SUBROUTINE Connect_GetNetForceAndMass(Connect, rRef, Fnet_out, M_out, m, p) + SUBROUTINE Point_GetNetForceAndMass(Point, rRef, Fnet_out, M_out, m, p) - Type(MD_Connect), INTENT(INOUT) :: Connect ! the Connect object + Type(MD_Point), INTENT(INOUT) :: Point ! the Point object Real(DbKi), INTENT(IN ) :: rRef(3) ! global coordinates of reference point (i.e. the parent body) Real(DbKi), INTENT( OUT) :: Fnet_out(6) ! force and moment vector about rRef Real(DbKi), INTENT( OUT) :: M_out(6,6) ! mass and inertia matrix about rRef TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects TYPE(MD_ParameterType),INTENT(IN ) :: p ! Parameters - Real(DbKi) :: rRel( 3) ! position of connection relative to the body reference point (global orientation frame) + Real(DbKi) :: rRel( 3) ! position of point relative to the body reference point (global orientation frame) - CALL Connect_DoRHS(Connect, m, p) + CALL Point_DoRHS(Point, m, p) - rRel = Connect%r - rRef ! vector from body reference point to node + rRel = Point%r - rRef ! vector from body reference point to node ! convert net force into 6dof force about body ref point - CALL translateForce3to6DOF(rRel, Connect%Fnet, Fnet_out) + CALL translateForce3to6DOF(rRel, Point%Fnet, Fnet_out) ! convert mass matrix to 6by6 mass matrix about body ref point - CALL translateMass3to6DOF(rRel, Connect%M, M_out) + CALL translateMass3to6DOF(rRel, Point%M, M_out) - END SUBROUTINE Connect_GetNetForceAndMass + END SUBROUTINE Point_GetNetForceAndMass ! this function handles assigning a line to a connection node !-------------------------------------------------------------- - SUBROUTINE Connect_AddLine(Connect, lineID, TopOfLine) + SUBROUTINE Point_AddLine(Point, lineID, TopOfLine) - Type(MD_Connect), INTENT (INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT (INOUT) :: Point ! the Point object Integer(IntKi), INTENT( IN ) :: lineID Integer(IntKi), INTENT( IN ) :: TopOfLine - IF (wordy > 0) Print*, "L", lineID, "->C", Connect%IdNum + IF (wordy > 0) Print*, "L", lineID, "->C", Point%IdNum - IF (Connect%nAttached <10) THEN ! this is currently just a maximum imposed by a fixed array size. could be improved. - Connect%nAttached = Connect%nAttached + 1 ! add the line to the number connected - Connect%Attached(Connect%nAttached) = lineID - Connect%Top(Connect%nAttached) = TopOfLine ! attached to line ... 1 = top/fairlead(end B), 0 = bottom/anchor(end A) + IF (Point%nAttached <10) THEN ! this is currently just a maximum imposed by a fixed array size. could be improved. + Point%nAttached = Point%nAttached + 1 ! add the line to the number connected + Point%Attached(Point%nAttached) = lineID + Point%Top(Point%nAttached) = TopOfLine ! attached to line ... 1 = top/fairlead(end B), 0 = bottom/anchor(end A) ELSE - Print*, "Too many lines connected to Point ", Connect%IdNum, " in MoorDyn!" + Print*, "Too many lines connected to Point ", Point%IdNum, " in MoorDyn!" END IF - END SUBROUTINE Connect_AddLine + END SUBROUTINE Point_AddLine ! this function handles removing a line from a connection node !-------------------------------------------------------------- - SUBROUTINE Connect_RemoveLine(Connect, lineID, TopOfLine, rEnd, rdEnd) + SUBROUTINE Point_RemoveLine(Point, lineID, TopOfLine, rEnd, rdEnd) - Type(MD_Connect), INTENT (INOUT) :: Connect ! the Connection object + Type(MD_Point), INTENT (INOUT) :: Point ! the Point object Integer(IntKi), INTENT( IN ) :: lineID Integer(IntKi), INTENT( OUT) :: TopOfLine REAL(DbKi), INTENT(INOUT) :: rEnd(3) @@ -380,39 +380,39 @@ SUBROUTINE Connect_RemoveLine(Connect, lineID, TopOfLine, rEnd, rdEnd) Integer(IntKi) :: l,m,J - DO l = 1,Connect%nAttached ! look through attached lines + DO l = 1,Point%nAttached ! look through attached lines - IF (Connect%Attached(l) == lineID) THEN ! if this is the line's entry in the attachment list + IF (Point%Attached(l) == lineID) THEN ! if this is the line's entry in the attachment list - TopOfLine = Connect%Top(l); ! record which end of the line was attached + TopOfLine = Point%Top(l); ! record which end of the line was attached - DO m = l,Connect%nAttached-1 + DO m = l,Point%nAttached-1 - Connect%Attached(m) = Connect%Attached(m+1) ! move subsequent line links forward one spot in the list to eliminate this line link - Connect%Top( m) = Connect%Top(m+1) + Point%Attached(m) = Point%Attached(m+1) ! move subsequent line links forward one spot in the list to eliminate this line link + Point%Top( m) = Point%Top(m+1) - Connect%nAttached = Connect%nAttached - 1 ! reduce attached line counter by 1 + Point%nAttached = Point%nAttached - 1 ! reduce attached line counter by 1 ! also pass back the kinematics at the end DO J = 1,3 - rEnd( J) = Connect%r( J) - rdEnd(J) = Connect%rd(J) + rEnd( J) = Point%r( J) + rdEnd(J) = Point%rd(J) END DO - print*, "Detached line ", lineID, " from Connection ", Connect%IdNum + print*, "Detached line ", lineID, " from Point ", Point%IdNum EXIT END DO - IF (l == Connect%nAttached) THEN ! detect if line not found - print *, "Error: failed to find line to remove during removeLineFromConnect call to connection ", Connect%IdNum, ". Line ", lineID + IF (l == Point%nAttached) THEN ! detect if line not found + print *, "Error: failed to find line to remove during removeLineFromPoint call to point ", Point%IdNum, ". Line ", lineID END IF END IF END DO - END SUBROUTINE Connect_RemoveLine + END SUBROUTINE Point_RemoveLine diff --git a/modules/moordyn/src/MoorDyn_Registry.txt b/modules/moordyn/src/MoorDyn_Registry.txt index a3ed6ef2b9..60a78f2676 100644 --- a/modules/moordyn/src/MoorDyn_Registry.txt +++ b/modules/moordyn/src/MoorDyn_Registry.txt @@ -50,7 +50,7 @@ typedef ^ ^ DbKi WaveTime # nvm typedef ^ ^ MeshType FarmCoupledKinematics {:} - - "array of input kinematics meshes from each of the turbine-level MoorDyn instances" "[m, m/s]" # nvm typedef ^ ^ IntKi FarmNCpldBodies {:} - - "" "" # nvm typedef ^ ^ IntKi FarmNCpldRods {:} - - "" "" -# nvm typedef ^ ^ IntKi FarmNCpldCons {:} - - "number of Fairlead Connections" "" +# nvm typedef ^ ^ IntKi FarmNCpldPoints {:} - - "number of Fairlead Points" "" # ====================================== Internal data types ======================================================================== # line properties from line dictionary input @@ -91,19 +91,19 @@ typedef ^ ^ DbKi CdEnd - typedef ^ ^ DbKi CaEnd - - - "added mass coefficient for rod end" "[-]" # this is the Body type, which holds data for each body object -typedef ^ MD_Body IntKi IdNum - - - "integer identifier of this Connection" -typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=connect" -typedef ^ ^ IntKi AttachedC {30} - - "list of IdNums of connections attached to this body" +typedef ^ MD_Body IntKi IdNum - - - "integer identifier of this Point" +typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=point" +typedef ^ ^ IntKi AttachedC {30} - - "list of IdNums of points attached to this body" typedef ^ ^ IntKi AttachedR {30} - - "list of IdNums of rods attached to this body" -typedef ^ ^ IntKi nAttachedC - 0 - "number of attached connections" +typedef ^ ^ IntKi nAttachedC - 0 - "number of attached points" typedef ^ ^ IntKi nAttachedR - 0 - "number of attached rods" -typedef ^ ^ DbKi rConnectRel {3}{30} - - "relative position of connection on body" +typedef ^ ^ DbKi rPointRel {3}{30} - - "relative position of point on body" typedef ^ ^ DbKi r6RodRel {6}{30} - - "relative position and orientation of rod on body" typedef ^ ^ DbKi bodyM - - - "" typedef ^ ^ DbKi bodyV - - - "" typedef ^ ^ DbKi bodyI {3} - - "" -typedef ^ ^ DbKi bodyCdA {6} - - "product of drag force and frontal area of connection point" "[m^2]" -typedef ^ ^ DbKi bodyCa {6} - - "added mass coefficient of connection point" "-" +typedef ^ ^ DbKi bodyCdA {6} - - "product of drag force and frontal area of point point" "[m^2]" +typedef ^ ^ DbKi bodyCa {6} - - "added mass coefficient of point point" "-" typedef ^ ^ DbKi time - - - "current time" "[s]" typedef ^ ^ DbKi r6 {6} - - "position" typedef ^ ^ DbKi v6 {6} - - "velocity" @@ -118,20 +118,20 @@ typedef ^ ^ DbKi M0 {6}{6} typedef ^ ^ DbKi OrMat {3}{3} - - "DCM for body orientation" typedef ^ ^ DbKi rCG {3} - - "vector in body frame from ref point to CG (before rods etc..)" -# this is the Connection type, which holds data for each connection object -typedef ^ MD_Connect IntKi IdNum - - - "integer identifier of this Connection" -typedef ^ ^ CHARACTER(10) type - - - "type of Connect: fix, vessel, connect" -typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=connect" -typedef ^ ^ IntKi Attached {10} - - "list of IdNums of lines attached to this connection node" +# this is the Point type, which holds data for each point object +typedef ^ MD_Point IntKi IdNum - - - "integer identifier of this Point" +typedef ^ ^ CHARACTER(10) type - - - "type of Point: fix, vessel, point" +typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=point" +typedef ^ ^ IntKi Attached {10} - - "list of IdNums of lines attached to this point node" typedef ^ ^ IntKi Top {10} - - "list of ints specifying whether each line is attached at 1 = top/fairlead(end B), 0 = bottom/anchor(end A)" typedef ^ ^ IntKi nAttached - 0 - "number of attached lines" -typedef ^ ^ DbKi conM - - - "" -typedef ^ ^ DbKi conV - - - "" -typedef ^ ^ DbKi conFX - - - "" -typedef ^ ^ DbKi conFY - - - "" -typedef ^ ^ DbKi conFZ - - - "" -typedef ^ ^ DbKi conCa - - - "added mass coefficient of connection point" "-" -typedef ^ ^ DbKi conCdA - - - "product of drag force and frontal area of connection point" "[m^2]" +typedef ^ ^ DbKi pointM - - - "" +typedef ^ ^ DbKi pointV - - - "" +typedef ^ ^ DbKi pointFX - - - "" +typedef ^ ^ DbKi pointFY - - - "" +typedef ^ ^ DbKi pointFZ - - - "" +typedef ^ ^ DbKi pointCa - - - "added mass coefficient of point point" "-" +typedef ^ ^ DbKi pointCdA - - - "product of drag force and frontal area of point point" "[m^2]" typedef ^ ^ DbKi time - - - "current time" "[s]" typedef ^ ^ DbKi r {3} - - "position" typedef ^ ^ DbKi rd {3} - - "velocity" @@ -147,7 +147,7 @@ typedef ^ ^ DbKi M {3}{3} typedef ^ MD_Rod IntKi IdNum - - - "integer identifier of this Line" typedef ^ ^ CHARACTER(10) type - - - "type of Rod. should match one of RodProp names" typedef ^ ^ IntKi PropsIdNum - - - "the IdNum of the associated rod properties" - -typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=connect" +typedef ^ ^ IntKi typeNum - - - "integer identifying the type. 0=fixed, 1=vessel, 2=point" typedef ^ ^ IntKi AttachedA {10} - - "list of IdNums of lines attached to end A" typedef ^ ^ IntKi AttachedB {10} - - "list of IdNums of lines attached to end B" typedef ^ ^ IntKi TopA {10} - - "list of ints specifying whether each line is attached at 1 = top/fairlead(end B), 0 = bottom/anchor(end A)" @@ -156,8 +156,8 @@ typedef ^ ^ IntKi nAttachedA - typedef ^ ^ IntKi nAttachedB - 0 - "number of attached lines to Rod end B" typedef ^ ^ IntKi OutFlagList {20} - - "array specifying what line quantities should be output (1 vs 0)" - typedef ^ ^ IntKi N - - - "The number of elements in the line" - -typedef ^ ^ IntKi endTypeA - - - "type of connection at end A: 0=pinned to Connection, 1=cantilevered to Rod." - -typedef ^ ^ IntKi endTypeB - - - "type of connection at end B: 0=pinned to Connection, 1=cantilevered to Rod." - +typedef ^ ^ IntKi endTypeA - - - "type of point at end A: 0=pinned to Point, 1=cantilevered to Rod." - +typedef ^ ^ IntKi endTypeB - - - "type of point at end B: 0=pinned to Point, 1=cantilevered to Rod." - typedef ^ ^ DbKi UnstrLen - - - "length of the rod" "[m]" typedef ^ ^ DbKi mass - - - "mass of the rod" "[kg]" typedef ^ ^ DbKi rho - - - "density" "[kg/m3]" @@ -211,11 +211,11 @@ typedef ^ ^ IntKi PropsIdNum - typedef ^ ^ IntKi ElasticMod - - - "Which elasticity model to use: {0 basic, 1 viscoelastic, 2 future SYCOM} " - typedef ^ ^ IntKi OutFlagList {20} - - "array specifying what line quantities should be output (1 vs 0)" - typedef ^ ^ IntKi CtrlChan - 0 - "index of control channel that will drive line active tensioning (0 for none)" - -typedef ^ ^ IntKi FairConnect - - - "IdNum of Connection at fairlead" -typedef ^ ^ IntKi AnchConnect - - - "IdNum of Connection at anchor" +typedef ^ ^ IntKi FairPoint - - - "IdNum of Point at fairlead" +typedef ^ ^ IntKi AnchPoint - - - "IdNum of Point at anchor" typedef ^ ^ IntKi N - - - "The number of elements in the line" - -typedef ^ ^ IntKi endTypeA - - - "type of connection at end A: 0=pinned to Connection, 1=cantilevered to Rod." - -typedef ^ ^ IntKi endTypeB - - - "type of connection at end B: 0=pinned to Connection, 1=cantilevered to Rod." - +typedef ^ ^ IntKi endTypeA - - - "type of connection at end A: 0=pinned to Point, 1=cantilevered to Rod." - +typedef ^ ^ IntKi endTypeB - - - "type of connection at end B: 0=pinned to Point, 1=cantilevered to Rod." - typedef ^ ^ DbKi UnstrLen - - - "unstretched length of the line" - typedef ^ ^ DbKi rho - - - "density" "[kg/m3]" typedef ^ ^ DbKi d - - - "volume-equivalent diameter" "[m]" @@ -278,9 +278,9 @@ typedef ^ MD_Fail IntKi IdNum - typedef ^ MD_OutParmType CHARACTER(10) Name - - - "name of output channel" typedef ^ ^ CHARACTER(10) Units - - - "units string" typedef ^ ^ IntKi QType - - - "type of quantity - 0=tension, 1=x, 2=y, 3=z..." -typedef ^ ^ IntKi OType - - - "type of object - 0=line, 1=connect" +typedef ^ ^ IntKi OType - - - "type of object - 0=line, 1=point" typedef ^ ^ IntKi NodeID - - - "node number if OType=0. 0=anchor, -1=N=Fairlead" -typedef ^ ^ IntKi ObjID - - - "number of Connect or Line object" +typedef ^ ^ IntKi ObjID - - - "number of Point or Line object" ## ============================== Define Initialization outputs here: ================================================================================================================================ @@ -315,22 +315,22 @@ typedef ^ OtherStateType SiKi dummy - ## ============================== Define Misc variables here: ===================================================================================================================================== typedef ^ MiscVarType MD_LineProp LineTypeList {:} - - "array of properties for each line type" - typedef ^ ^ MD_RodProp RodTypeList {:} - - "array of properties for each rod type" - -typedef ^ ^ MD_Body GroundBody - - - "the single ground body which is the parent of all stationary connections" - +typedef ^ ^ MD_Body GroundBody - - - "the single ground body which is the parent of all stationary points" - typedef ^ ^ MD_Body BodyList {:} - - "array of body objects" - typedef ^ ^ MD_Rod RodList {:} - - "array of rod objects" - -typedef ^ ^ MD_Connect ConnectList {:} - - "array of connection objects" - +typedef ^ ^ MD_Point PointList {:} - - "array of point objects" - typedef ^ ^ MD_Line LineList {:} - - "array of line objects" - typedef ^ ^ MD_Fail FailList {:} - - "array of line objects" - -typedef ^ ^ IntKi FreeConIs {:} - - "array of free connection indices in ConnectList vector" "" -typedef ^ ^ IntKi CpldConIs {:}{:} - - "array of coupled/fairlead connection indices in ConnectList vector" "" +typedef ^ ^ IntKi FreePointIs {:} - - "array of free point indices in PointList vector" "" +typedef ^ ^ IntKi CpldPointIs {:}{:} - - "array of coupled/fairlead point indices in PointList vector" "" typedef ^ ^ IntKi FreeRodIs {:} - - "array of free rod indices in RodList vector" "" typedef ^ ^ IntKi CpldRodIs {:}{:} - - "array of coupled/fairlead rod indices in RodList vector" "" typedef ^ ^ IntKi FreeBodyIs {:} - - "array of free body indices in BodyList vector" "" typedef ^ ^ IntKi CpldBodyIs {:}{:} - - "array of coupled body indices in BodyList vector" "" typedef ^ ^ IntKi LineStateIs1 {:} - - "starting index of each line's states in state vector" "" typedef ^ ^ IntKi LineStateIsN {:} - - "ending index of each line's states in state vector" "" -typedef ^ ^ IntKi ConStateIs1 {:} - - "starting index of each line's states in state vector" "" -typedef ^ ^ IntKi ConStateIsN {:} - - "ending index of each line's states in state vector" "" +typedef ^ ^ IntKi PointStateIs1 {:} - - "starting index of each line's states in state vector" "" +typedef ^ ^ IntKi PointStateIsN {:} - - "ending index of each line's states in state vector" "" typedef ^ ^ IntKi RodStateIs1 {:} - - "starting index of each rod's states in state vector" "" typedef ^ ^ IntKi RodStateIsN {:} - - "ending index of each rod's states in state vector" "" typedef ^ ^ IntKi BodyStateIs1 {:} - - "starting index of each body's states in state vector" "" @@ -352,8 +352,8 @@ typedef ^ ^ IntKi BathGrid_npoints {:} ## ============================== Parameters ============================================================================================================================================ typedef ^ ParameterType IntKi nLineTypes - 0 - "number of line types" "" typedef ^ ^ IntKi nRodTypes - 0 - "number of rod types" "" -typedef ^ ^ IntKi nConnects - 0 - "number of Connection objects" "" -typedef ^ ^ IntKi nConnectsExtra - 0 - "number of Connection objects including space for extra ones that could arise from line failures" "" +typedef ^ ^ IntKi nPoints - 0 - "number of Point objects" "" +typedef ^ ^ IntKi nPointsExtra - 0 - "number of Point objects including space for extra ones that could arise from line failures" "" typedef ^ ^ IntKi nBodies - 0 - "number of Body objects" "" typedef ^ ^ IntKi nRods - 0 - "number of Rod objects" "" typedef ^ ^ IntKi nLines - 0 - "number of Line objects" "" @@ -361,12 +361,12 @@ typedef ^ ^ IntKi nCtrlChans - typedef ^ ^ IntKi nFails - 0 - "number of failure conditions" "" typedef ^ ^ IntKi nFreeBodies - 0 - "" "" typedef ^ ^ IntKi nFreeRods - 0 - "" "" -typedef ^ ^ IntKi nFreeCons - 0 - "" "" +typedef ^ ^ IntKi nFreePoints - 0 - "" "" typedef ^ ^ IntKi nCpldBodies {:} - - "number of coupled bodies (for FAST.Farm, size>1 with an entry for each turbine)" "" typedef ^ ^ IntKi nCpldRods {:} - - "number of coupled rods (for FAST.Farm, size>1 with an entry for each turbine)" "" -typedef ^ ^ IntKi nCpldCons {:} - - "number of coupled points (for FAST.Farm, size>1 with an entry for each turbine)" "" -typedef ^ ^ IntKi NConns - 0 - "number of Connect type Connections - not to be confused with NConnects" "" -typedef ^ ^ IntKi NAnchs - 0 - "number of Anchor type Connections" "" +typedef ^ ^ IntKi nCpldPoints {:} - - "number of coupled points (for FAST.Farm, size>1 with an entry for each turbine)" "" +typedef ^ ^ IntKi NConns - 0 - "number of Connect type Points - not to be confused with NPoints" "" +typedef ^ ^ IntKi NAnchs - 0 - "number of Anchor type Points" "" typedef ^ ^ DbKi Tmax - - - "simulation duration" "[s]" typedef ^ ^ DbKi g - 9.81 - "gravitational constant (positive)" "[m/s^2]" typedef ^ ^ DbKi rhoW - 1025 - "density of seawater" "[kg/m^3]" diff --git a/modules/moordyn/src/MoorDyn_Rod.f90 b/modules/moordyn/src/MoorDyn_Rod.f90 index 26bd00c96b..0ae6d79161 100644 --- a/modules/moordyn/src/MoorDyn_Rod.f90 +++ b/modules/moordyn/src/MoorDyn_Rod.f90 @@ -207,7 +207,7 @@ SUBROUTINE Rod_Initialize(Rod, states, m) ! r and rd of ends have already been set by setup function or by parent object <<<<< right? <<<<< - ! Pass kinematics to any attached lines (this is just like what a Connection does, except for both ends) + ! Pass kinematics to any attached lines (this is just like what a Point does, except for both ends) ! so that they have the correct initial positions at this initialization stage. if (Rod%typeNum >- 2) CALL Rod_SetDependentKin(Rod, 0.0_DbKi, m, .TRUE.) ! don't call this for type -2 coupled Rods as it's already been called @@ -357,7 +357,7 @@ SUBROUTINE Rod_SetDependentKin(Rod, t, m, initial) Type(MD_Rod), INTENT(INOUT) :: Rod ! the Rod object Real(DbKi), INTENT(IN ) :: t ! instantaneous time - TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Connections) + TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Points) LOGICAL, INTENT(IN ) :: initial ! true if this is the call during initialization (in which case avoid calling any Lines yet) INTEGER(IntKi) :: l ! index of segments or nodes along line @@ -390,7 +390,7 @@ SUBROUTINE Rod_SetDependentKin(Rod, t, m, initial) CALL transformKinematicsAtoB(Rod%r6(1:3), Rod%r6(4:6), Rod%UnstrLen, Rod%v6, Rod%r(:,N), Rod%rd(:,N)) ! end B end if - ! pass end node kinematics to any attached lines (this is just like what a Connection does, except for both ends) + ! pass end node kinematics to any attached lines (this is just like what a Point does, except for both ends) DO l=1,Rod%nAttachedA CALL Line_SetEndKinematics(m%LineList(Rod%attachedA(l)), Rod%r(:,0), Rod%rd(:,0), t, Rod%TopA(l)) END DO @@ -424,7 +424,7 @@ SUBROUTINE Rod_SetDependentKin(Rod, t, m, initial) Rod%r6(4:6) = Rod%q ! set orientation angles END IF - ! pass Rod orientation to any attached lines (this is just like what a Connection does, except for both ends) + ! pass Rod orientation to any attached lines (this is just like what a Point does, except for both ends) DO l=1,Rod%nAttachedA CALL Line_SetEndOrientation(m%LineList(Rod%attachedA(l)), Rod%q, Rod%TopA(l), 0) END DO @@ -440,7 +440,7 @@ SUBROUTINE Rod_GetStateDeriv(Rod, Xd, m, p) Type(MD_Rod), INTENT(INOUT) :: Rod ! the Rod object Real(DbKi), INTENT(INOUT) :: Xd(:) ! state derivative vector section for this line - TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Connections) + TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! passing along all mooring objects (for simplicity, since Bodies deal with Rods and Points) TYPE(MD_ParameterType),INTENT(IN ) :: p ! Parameters !TYPE(MD_MiscVarType), INTENT(INOUT) :: m ! misc/optimization variables @@ -1069,10 +1069,10 @@ END SUBROUTINE Rod_GetNetForceAndMass !-------------------------------------------------------------- - ! this function handles assigning a line to a connection node + ! this function handles assigning a line to a point node SUBROUTINE Rod_AddLine(Rod, lineID, TopOfLine, endB) - Type(MD_Rod), INTENT (INOUT) :: Rod ! the Connection object + Type(MD_Rod), INTENT (INOUT) :: Rod ! the Point object Integer(IntKi), INTENT( IN ) :: lineID Integer(IntKi), INTENT( IN ) :: TopOfLine @@ -1107,10 +1107,10 @@ SUBROUTINE Rod_AddLine(Rod, lineID, TopOfLine, endB) END SUBROUTINE Rod_AddLine - ! this function handles removing a line from a connection node + ! this function handles removing a line from a point node SUBROUTINE Rod_RemoveLine(Rod, lineID, TopOfLine, endB, rEnd, rdEnd) - Type(MD_Rod), INTENT (INOUT) :: Rod ! the Connection object + Type(MD_Rod), INTENT (INOUT) :: Rod ! the Point object Integer(IntKi), INTENT( IN ) :: lineID Integer(IntKi), INTENT( OUT) :: TopOfLine diff --git a/modules/moordyn/src/MoorDyn_Types.f90 b/modules/moordyn/src/MoorDyn_Types.f90 index b35edada02..aac971f517 100644 --- a/modules/moordyn/src/MoorDyn_Types.f90 +++ b/modules/moordyn/src/MoorDyn_Types.f90 @@ -107,19 +107,19 @@ MODULE MoorDyn_Types ! ======================= ! ========= MD_Body ======= TYPE, PUBLIC :: MD_Body - INTEGER(IntKi) :: IdNum !< integer identifier of this Connection [-] - INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=connect [-] - INTEGER(IntKi) , DIMENSION(1:30) :: AttachedC !< list of IdNums of connections attached to this body [-] + INTEGER(IntKi) :: IdNum !< integer identifier of this point [-] + INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=point [-] + INTEGER(IntKi) , DIMENSION(1:30) :: AttachedC !< list of IdNums of points attached to this body [-] INTEGER(IntKi) , DIMENSION(1:30) :: AttachedR !< list of IdNums of rods attached to this body [-] - INTEGER(IntKi) :: nAttachedC = 0 !< number of attached connections [-] + INTEGER(IntKi) :: nAttachedC = 0 !< number of attached points [-] INTEGER(IntKi) :: nAttachedR = 0 !< number of attached rods [-] - REAL(DbKi) , DIMENSION(1:3,1:30) :: rConnectRel !< relative position of connection on body [-] + REAL(DbKi) , DIMENSION(1:3,1:30) :: rPointRel !< relative position of point on body [-] REAL(DbKi) , DIMENSION(1:6,1:30) :: r6RodRel !< relative position and orientation of rod on body [-] REAL(DbKi) :: bodyM !< [-] REAL(DbKi) :: bodyV !< [-] REAL(DbKi) , DIMENSION(1:3) :: bodyI !< [-] - REAL(DbKi) , DIMENSION(1:6) :: bodyCdA !< product of drag force and frontal area of connection point [[m^2]] - REAL(DbKi) , DIMENSION(1:6) :: bodyCa !< added mass coefficient of connection point [-] + REAL(DbKi) , DIMENSION(1:6) :: bodyCdA !< product of drag force and frontal area of point [[m^2]] + REAL(DbKi) , DIMENSION(1:6) :: bodyCa !< added mass coefficient o point [-] REAL(DbKi) :: time !< current time [[s]] REAL(DbKi) , DIMENSION(1:6) :: r6 !< position [-] REAL(DbKi) , DIMENSION(1:6) :: v6 !< velocity [-] @@ -135,21 +135,21 @@ MODULE MoorDyn_Types REAL(DbKi) , DIMENSION(1:3) :: rCG !< vector in body frame from ref point to CG (before rods etc..) [-] END TYPE MD_Body ! ======================= -! ========= MD_Connect ======= - TYPE, PUBLIC :: MD_Connect - INTEGER(IntKi) :: IdNum !< integer identifier of this Connection [-] - CHARACTER(10) :: type !< type of Connect: fix, vessel, connect [-] - INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=connect [-] - INTEGER(IntKi) , DIMENSION(1:10) :: Attached !< list of IdNums of lines attached to this connection node [-] +! ========= MD_Point ======= + TYPE, PUBLIC :: MD_Point + INTEGER(IntKi) :: IdNum !< integer identifier of this point [-] + CHARACTER(10) :: type !< type of Point: fix, vessel, point [-] + INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=point [-] + INTEGER(IntKi) , DIMENSION(1:10) :: Attached !< list of IdNums of lines attached to this point node [-] INTEGER(IntKi) , DIMENSION(1:10) :: Top !< list of ints specifying whether each line is attached at 1 = top/fairlead(end B), 0 = bottom/anchor(end A) [-] INTEGER(IntKi) :: nAttached = 0 !< number of attached lines [-] - REAL(DbKi) :: conM !< [-] - REAL(DbKi) :: conV !< [-] - REAL(DbKi) :: conFX !< [-] - REAL(DbKi) :: conFY !< [-] - REAL(DbKi) :: conFZ !< [-] - REAL(DbKi) :: conCa !< added mass coefficient of connection point [-] - REAL(DbKi) :: conCdA !< product of drag force and frontal area of connection point [[m^2]] + REAL(DbKi) :: pointM !< [-] + REAL(DbKi) :: pointV !< [-] + REAL(DbKi) :: pointFX !< [-] + REAL(DbKi) :: pointFY !< [-] + REAL(DbKi) :: pointFZ !< [-] + REAL(DbKi) :: pointCa !< added mass coefficient of point [-] + REAL(DbKi) :: pointCdA !< product of drag force and frontal area of point [[m^2]] REAL(DbKi) :: time !< current time [[s]] REAL(DbKi) , DIMENSION(1:3) :: r !< position [-] REAL(DbKi) , DIMENSION(1:3) :: rd !< velocity [-] @@ -160,14 +160,14 @@ MODULE MoorDyn_Types REAL(DbKi) , DIMENSION(:), ALLOCATABLE :: PDyn !< water dynamic pressure at node [[Pa]] REAL(DbKi) , DIMENSION(1:3) :: Fnet !< total force on node (excluding inertial loads) [-] REAL(DbKi) , DIMENSION(1:3,1:3) :: M !< node mass matrix, from attached lines [-] - END TYPE MD_Connect + END TYPE MD_Point ! ======================= ! ========= MD_Rod ======= TYPE, PUBLIC :: MD_Rod INTEGER(IntKi) :: IdNum !< integer identifier of this Line [-] CHARACTER(10) :: type !< type of Rod. should match one of RodProp names [-] INTEGER(IntKi) :: PropsIdNum !< the IdNum of the associated rod properties [-] - INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=connect [-] + INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=point [-] INTEGER(IntKi) , DIMENSION(1:10) :: AttachedA !< list of IdNums of lines attached to end A [-] INTEGER(IntKi) , DIMENSION(1:10) :: AttachedB !< list of IdNums of lines attached to end B [-] INTEGER(IntKi) , DIMENSION(1:10) :: TopA !< list of ints specifying whether each line is attached at 1 = top/fairlead(end B), 0 = bottom/anchor(end A) [-] @@ -176,8 +176,8 @@ MODULE MoorDyn_Types INTEGER(IntKi) :: nAttachedB = 0 !< number of attached lines to Rod end B [-] INTEGER(IntKi) , DIMENSION(1:20) :: OutFlagList !< array specifying what line quantities should be output (1 vs 0) [-] INTEGER(IntKi) :: N !< The number of elements in the line [-] - INTEGER(IntKi) :: endTypeA !< type of connection at end A: 0=pinned to Connection, 1=cantilevered to Rod. [-] - INTEGER(IntKi) :: endTypeB !< type of connection at end B: 0=pinned to Connection, 1=cantilevered to Rod. [-] + INTEGER(IntKi) :: endTypeA !< type of point at end A: 0=pinned to point, 1=cantilevered to Rod. [-] + INTEGER(IntKi) :: endTypeB !< type of point at end B: 0=pinned to point, 1=cantilevered to Rod. [-] REAL(DbKi) :: UnstrLen !< length of the rod [[m]] REAL(DbKi) :: mass !< mass of the rod [[kg]] REAL(DbKi) :: rho !< density [[kg/m3]] @@ -231,11 +231,11 @@ MODULE MoorDyn_Types INTEGER(IntKi) :: ElasticMod !< Which elasticity model to use: {0 basic, 1 viscoelastic, 2 future SYCOM} [-] INTEGER(IntKi) , DIMENSION(1:20) :: OutFlagList !< array specifying what line quantities should be output (1 vs 0) [-] INTEGER(IntKi) :: CtrlChan = 0 !< index of control channel that will drive line active tensioning (0 for none) [-] - INTEGER(IntKi) :: FairConnect !< IdNum of Connection at fairlead [-] - INTEGER(IntKi) :: AnchConnect !< IdNum of Connection at anchor [-] + INTEGER(IntKi) :: FairPoint !< IdNum of point at fairlead [-] + INTEGER(IntKi) :: AnchPoint !< IdNum of point at anchor [-] INTEGER(IntKi) :: N !< The number of elements in the line [-] - INTEGER(IntKi) :: endTypeA !< type of connection at end A: 0=pinned to Connection, 1=cantilevered to Rod. [-] - INTEGER(IntKi) :: endTypeB !< type of connection at end B: 0=pinned to Connection, 1=cantilevered to Rod. [-] + INTEGER(IntKi) :: endTypeA !< type of point at end A: 0=pinned to point, 1=cantilevered to Rod. [-] + INTEGER(IntKi) :: endTypeB !< type of point at end B: 0=pinned to point, 1=cantilevered to Rod. [-] REAL(DbKi) :: UnstrLen !< unstretched length of the line [-] REAL(DbKi) :: rho !< density [[kg/m3]] REAL(DbKi) :: d !< volume-equivalent diameter [[m]] @@ -301,9 +301,9 @@ MODULE MoorDyn_Types CHARACTER(10) :: Name !< name of output channel [-] CHARACTER(10) :: Units !< units string [-] INTEGER(IntKi) :: QType !< type of quantity - 0=tension, 1=x, 2=y, 3=z... [-] - INTEGER(IntKi) :: OType !< type of object - 0=line, 1=connect [-] - INTEGER(IntKi) :: NodeID !< node number if OType=0. 0=anchor, -1=N=Fairlead [-] - INTEGER(IntKi) :: ObjID !< number of Connect or Line object [-] + INTEGER(IntKi) :: OType !< type of object - 0=line, 1=point [-] + INTEGER(IntKi) :: NodeID !< node number if OType=0. 0=anchor, -1=Whole Object [-] + INTEGER(IntKi) :: ObjID !< number of Point or Line object [-] END TYPE MD_OutParmType ! ======================= ! ========= MD_InitOutputType ======= @@ -346,22 +346,22 @@ MODULE MoorDyn_Types TYPE, PUBLIC :: MD_MiscVarType TYPE(MD_LineProp) , DIMENSION(:), ALLOCATABLE :: LineTypeList !< array of properties for each line type [-] TYPE(MD_RodProp) , DIMENSION(:), ALLOCATABLE :: RodTypeList !< array of properties for each rod type [-] - TYPE(MD_Body) :: GroundBody !< the single ground body which is the parent of all stationary connections [-] + TYPE(MD_Body) :: GroundBody !< the single ground body which is the parent of all stationary points [-] TYPE(MD_Body) , DIMENSION(:), ALLOCATABLE :: BodyList !< array of body objects [-] TYPE(MD_Rod) , DIMENSION(:), ALLOCATABLE :: RodList !< array of rod objects [-] - TYPE(MD_Connect) , DIMENSION(:), ALLOCATABLE :: ConnectList !< array of connection objects [-] + TYPE(MD_Point) , DIMENSION(:), ALLOCATABLE :: PointList !< array of point objects [-] TYPE(MD_Line) , DIMENSION(:), ALLOCATABLE :: LineList !< array of line objects [-] TYPE(MD_Fail) , DIMENSION(:), ALLOCATABLE :: FailList !< array of line objects [-] - INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: FreeConIs !< array of free connection indices in ConnectList vector [] - INTEGER(IntKi) , DIMENSION(:,:), ALLOCATABLE :: CpldConIs !< array of coupled/fairlead connection indices in ConnectList vector [] + INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: FreePointIs !< array of free point indices in PointList vector [] + INTEGER(IntKi) , DIMENSION(:,:), ALLOCATABLE :: CpldPointIs !< array of coupled/fairlead point indices in PointList vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: FreeRodIs !< array of free rod indices in RodList vector [] INTEGER(IntKi) , DIMENSION(:,:), ALLOCATABLE :: CpldRodIs !< array of coupled/fairlead rod indices in RodList vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: FreeBodyIs !< array of free body indices in BodyList vector [] INTEGER(IntKi) , DIMENSION(:,:), ALLOCATABLE :: CpldBodyIs !< array of coupled body indices in BodyList vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: LineStateIs1 !< starting index of each line's states in state vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: LineStateIsN !< ending index of each line's states in state vector [] - INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: ConStateIs1 !< starting index of each line's states in state vector [] - INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: ConStateIsN !< ending index of each line's states in state vector [] + INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: PointStateIs1 !< starting index of each point's states in state vector [] + INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: PointStateIsN !< ending index of each point's states in state vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: RodStateIs1 !< starting index of each rod's states in state vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: RodStateIsN !< ending index of each rod's states in state vector [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: BodyStateIs1 !< starting index of each body's states in state vector [] @@ -384,8 +384,8 @@ MODULE MoorDyn_Types TYPE, PUBLIC :: MD_ParameterType INTEGER(IntKi) :: nLineTypes = 0 !< number of line types [] INTEGER(IntKi) :: nRodTypes = 0 !< number of rod types [] - INTEGER(IntKi) :: nConnects = 0 !< number of Connection objects [] - INTEGER(IntKi) :: nConnectsExtra = 0 !< number of Connection objects including space for extra ones that could arise from line failures [] + INTEGER(IntKi) :: nPoints = 0 !< number of point objects [] + INTEGER(IntKi) :: nPointsExtra = 0 !< number of point objects including space for extra ones that could arise from line failures [] INTEGER(IntKi) :: nBodies = 0 !< number of Body objects [] INTEGER(IntKi) :: nRods = 0 !< number of Rod objects [] INTEGER(IntKi) :: nLines = 0 !< number of Line objects [] @@ -393,12 +393,12 @@ MODULE MoorDyn_Types INTEGER(IntKi) :: nFails = 0 !< number of failure conditions [] INTEGER(IntKi) :: nFreeBodies = 0 !< [] INTEGER(IntKi) :: nFreeRods = 0 !< [] - INTEGER(IntKi) :: nFreeCons = 0 !< [] + INTEGER(IntKi) :: nFreePoints = 0 !< [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: nCpldBodies !< number of coupled bodies (for FAST.Farm, size>1 with an entry for each turbine) [] INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: nCpldRods !< number of coupled rods (for FAST.Farm, size>1 with an entry for each turbine) [] - INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: nCpldCons !< number of coupled points (for FAST.Farm, size>1 with an entry for each turbine) [] + INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: nCpldPoints !< number of coupled points (for FAST.Farm, size>1 with an entry for each turbine) [] INTEGER(IntKi) :: NConns = 0 !< number of Connect type Connections - not to be confused with NConnects [] - INTEGER(IntKi) :: NAnchs = 0 !< number of Anchor type Connections [] + INTEGER(IntKi) :: NAnchs = 0 !< number of Anchor type points [] REAL(DbKi) :: Tmax !< simulation duration [[s]] REAL(DbKi) :: g = 9.81 !< gravitational constant (positive) [[m/s^2]] REAL(DbKi) :: rhoW = 1025 !< density of seawater [[kg/m^3]] @@ -1978,7 +1978,7 @@ SUBROUTINE MD_CopyBody( SrcBodyData, DstBodyData, CtrlCode, ErrStat, ErrMsg ) DstBodyData%AttachedR = SrcBodyData%AttachedR DstBodyData%nAttachedC = SrcBodyData%nAttachedC DstBodyData%nAttachedR = SrcBodyData%nAttachedR - DstBodyData%rConnectRel = SrcBodyData%rConnectRel + DstBodyData%rPointRel = SrcBodyData%rPointRel DstBodyData%r6RodRel = SrcBodyData%r6RodRel DstBodyData%bodyM = SrcBodyData%bodyM DstBodyData%bodyV = SrcBodyData%bodyV @@ -2064,7 +2064,7 @@ SUBROUTINE MD_PackBody( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz Int_BufSz = Int_BufSz + SIZE(InData%AttachedR) ! AttachedR Int_BufSz = Int_BufSz + 1 ! nAttachedC Int_BufSz = Int_BufSz + 1 ! nAttachedR - Db_BufSz = Db_BufSz + SIZE(InData%rConnectRel) ! rConnectRel + Db_BufSz = Db_BufSz + SIZE(InData%rPointRel) ! rPointRel Db_BufSz = Db_BufSz + SIZE(InData%r6RodRel) ! r6RodRel Db_BufSz = Db_BufSz + 1 ! bodyM Db_BufSz = Db_BufSz + 1 ! bodyV @@ -2127,9 +2127,9 @@ SUBROUTINE MD_PackBody( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz Int_Xferred = Int_Xferred + 1 IntKiBuf(Int_Xferred) = InData%nAttachedR Int_Xferred = Int_Xferred + 1 - DO i2 = LBOUND(InData%rConnectRel,2), UBOUND(InData%rConnectRel,2) - DO i1 = LBOUND(InData%rConnectRel,1), UBOUND(InData%rConnectRel,1) - DbKiBuf(Db_Xferred) = InData%rConnectRel(i1,i2) + DO i2 = LBOUND(InData%rPointRel,2), UBOUND(InData%rPointRel,2) + DO i1 = LBOUND(InData%rPointRel,1), UBOUND(InData%rPointRel,1) + DbKiBuf(Db_Xferred) = InData%rPointRel(i1,i2) Db_Xferred = Db_Xferred + 1 END DO END DO @@ -2261,13 +2261,13 @@ SUBROUTINE MD_UnPackBody( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) Int_Xferred = Int_Xferred + 1 OutData%nAttachedR = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - i1_l = LBOUND(OutData%rConnectRel,1) - i1_u = UBOUND(OutData%rConnectRel,1) - i2_l = LBOUND(OutData%rConnectRel,2) - i2_u = UBOUND(OutData%rConnectRel,2) - DO i2 = LBOUND(OutData%rConnectRel,2), UBOUND(OutData%rConnectRel,2) - DO i1 = LBOUND(OutData%rConnectRel,1), UBOUND(OutData%rConnectRel,1) - OutData%rConnectRel(i1,i2) = DbKiBuf(Db_Xferred) + i1_l = LBOUND(OutData%rPointRel,1) + i1_u = UBOUND(OutData%rPointRel,1) + i2_l = LBOUND(OutData%rPointRel,2) + i2_u = UBOUND(OutData%rPointRel,2) + DO i2 = LBOUND(OutData%rPointRel,2), UBOUND(OutData%rPointRel,2) + DO i1 = LBOUND(OutData%rPointRel,1), UBOUND(OutData%rPointRel,1) + OutData%rPointRel(i1,i2) = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 END DO END DO @@ -2391,9 +2391,9 @@ SUBROUTINE MD_UnPackBody( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) END DO END SUBROUTINE MD_UnPackBody - SUBROUTINE MD_CopyConnect( SrcConnectData, DstConnectData, CtrlCode, ErrStat, ErrMsg ) - TYPE(MD_Connect), INTENT(IN) :: SrcConnectData - TYPE(MD_Connect), INTENT(INOUT) :: DstConnectData + SUBROUTINE MD_CopyPoint( SrcPointData, DstPointData, CtrlCode, ErrStat, ErrMsg ) + TYPE(MD_Point), INTENT(IN) :: SrcPointData + TYPE(MD_Point), INTENT(INOUT) :: DstPointData INTEGER(IntKi), INTENT(IN ) :: CtrlCode INTEGER(IntKi), INTENT( OUT) :: ErrStat CHARACTER(*), INTENT( OUT) :: ErrMsg @@ -2403,48 +2403,48 @@ SUBROUTINE MD_CopyConnect( SrcConnectData, DstConnectData, CtrlCode, ErrStat, Er INTEGER(IntKi) :: i2, i2_l, i2_u ! bounds (upper/lower) for an array dimension 2 INTEGER(IntKi) :: ErrStat2 CHARACTER(ErrMsgLen) :: ErrMsg2 - CHARACTER(*), PARAMETER :: RoutineName = 'MD_CopyConnect' + CHARACTER(*), PARAMETER :: RoutineName = 'MD_CopyPoint' ! ErrStat = ErrID_None ErrMsg = "" - DstConnectData%IdNum = SrcConnectData%IdNum - DstConnectData%type = SrcConnectData%type - DstConnectData%typeNum = SrcConnectData%typeNum - DstConnectData%Attached = SrcConnectData%Attached - DstConnectData%Top = SrcConnectData%Top - DstConnectData%nAttached = SrcConnectData%nAttached - DstConnectData%conM = SrcConnectData%conM - DstConnectData%conV = SrcConnectData%conV - DstConnectData%conFX = SrcConnectData%conFX - DstConnectData%conFY = SrcConnectData%conFY - DstConnectData%conFZ = SrcConnectData%conFZ - DstConnectData%conCa = SrcConnectData%conCa - DstConnectData%conCdA = SrcConnectData%conCdA - DstConnectData%time = SrcConnectData%time - DstConnectData%r = SrcConnectData%r - DstConnectData%rd = SrcConnectData%rd - DstConnectData%a = SrcConnectData%a - DstConnectData%U = SrcConnectData%U - DstConnectData%Ud = SrcConnectData%Ud - DstConnectData%zeta = SrcConnectData%zeta -IF (ALLOCATED(SrcConnectData%PDyn)) THEN - i1_l = LBOUND(SrcConnectData%PDyn,1) - i1_u = UBOUND(SrcConnectData%PDyn,1) - IF (.NOT. ALLOCATED(DstConnectData%PDyn)) THEN - ALLOCATE(DstConnectData%PDyn(i1_l:i1_u),STAT=ErrStat2) - IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstConnectData%PDyn.', ErrStat, ErrMsg,RoutineName) + DstPointData%IdNum = SrcPointData%IdNum + DstPointData%type = SrcPointData%type + DstPointData%typeNum = SrcPointData%typeNum + DstPointData%Attached = SrcPointData%Attached + DstPointData%Top = SrcPointData%Top + DstPointData%nAttached = SrcPointData%nAttached + DstPointData%pointM = SrcPointData%pointM + DstPointData%pointV = SrcPointData%pointV + DstPointData%pointFX = SrcPointData%pointFX + DstPointData%pointFY = SrcPointData%pointFY + DstPointData%pointFZ = SrcPointData%pointFZ + DstPointData%pointCa = SrcPointData%pointCa + DstPointData%pointCdA = SrcPointData%pointCdA + DstPointData%time = SrcPointData%time + DstPointData%r = SrcPointData%r + DstPointData%rd = SrcPointData%rd + DstPointData%a = SrcPointData%a + DstPointData%U = SrcPointData%U + DstPointData%Ud = SrcPointData%Ud + DstPointData%zeta = SrcPointData%zeta +IF (ALLOCATED(SrcPointData%PDyn)) THEN + i1_l = LBOUND(SrcPointData%PDyn,1) + i1_u = UBOUND(SrcPointData%PDyn,1) + IF (.NOT. ALLOCATED(DstPointData%PDyn)) THEN + ALLOCATE(DstPointData%PDyn(i1_l:i1_u),STAT=ErrStat2) + IF (ErrStat2 /= 0) THEN + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstPointData%PDyn.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstConnectData%PDyn = SrcConnectData%PDyn + DstPointData%PDyn = SrcPointData%PDyn ENDIF - DstConnectData%Fnet = SrcConnectData%Fnet - DstConnectData%M = SrcConnectData%M - END SUBROUTINE MD_CopyConnect + DstPointData%Fnet = SrcPointData%Fnet + DstPointData%M = SrcPointData%M + END SUBROUTINE MD_CopyPoint - SUBROUTINE MD_DestroyConnect( ConnectData, ErrStat, ErrMsg, DEALLOCATEpointers ) - TYPE(MD_Connect), INTENT(INOUT) :: ConnectData + SUBROUTINE MD_DestroyPoint( PointData, ErrStat, ErrMsg, DEALLOCATEpointers ) + TYPE(MD_Point), INTENT(INOUT) :: PointData INTEGER(IntKi), INTENT( OUT) :: ErrStat CHARACTER(*), INTENT( OUT) :: ErrMsg LOGICAL,OPTIONAL,INTENT(IN ) :: DEALLOCATEpointers @@ -2453,7 +2453,7 @@ SUBROUTINE MD_DestroyConnect( ConnectData, ErrStat, ErrMsg, DEALLOCATEpointers ) LOGICAL :: DEALLOCATEpointers_local INTEGER(IntKi) :: ErrStat2 CHARACTER(ErrMsgLen) :: ErrMsg2 - CHARACTER(*), PARAMETER :: RoutineName = 'MD_DestroyConnect' + CHARACTER(*), PARAMETER :: RoutineName = 'MD_DestroyPoint' ErrStat = ErrID_None ErrMsg = "" @@ -2464,16 +2464,16 @@ SUBROUTINE MD_DestroyConnect( ConnectData, ErrStat, ErrMsg, DEALLOCATEpointers ) DEALLOCATEpointers_local = .true. END IF -IF (ALLOCATED(ConnectData%PDyn)) THEN - DEALLOCATE(ConnectData%PDyn) +IF (ALLOCATED(PointData%PDyn)) THEN + DEALLOCATE(PointData%PDyn) ENDIF - END SUBROUTINE MD_DestroyConnect + END SUBROUTINE MD_DestroyPoint - SUBROUTINE MD_PackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, SizeOnly ) + SUBROUTINE MD_PackPoint( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, SizeOnly ) REAL(ReKi), ALLOCATABLE, INTENT( OUT) :: ReKiBuf(:) REAL(DbKi), ALLOCATABLE, INTENT( OUT) :: DbKiBuf(:) INTEGER(IntKi), ALLOCATABLE, INTENT( OUT) :: IntKiBuf(:) - TYPE(MD_Connect), INTENT(IN) :: InData + TYPE(MD_Point), INTENT(IN) :: InData INTEGER(IntKi), INTENT( OUT) :: ErrStat CHARACTER(*), INTENT( OUT) :: ErrMsg LOGICAL,OPTIONAL, INTENT(IN ) :: SizeOnly @@ -2488,7 +2488,7 @@ SUBROUTINE MD_PackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, LOGICAL :: OnlySize ! if present and true, do not pack, just allocate buffers INTEGER(IntKi) :: ErrStat2 CHARACTER(ErrMsgLen) :: ErrMsg2 - CHARACTER(*), PARAMETER :: RoutineName = 'MD_PackConnect' + CHARACTER(*), PARAMETER :: RoutineName = 'MD_PackPoint' ! buffers to store subtypes, if any REAL(ReKi), ALLOCATABLE :: Re_Buf(:) REAL(DbKi), ALLOCATABLE :: Db_Buf(:) @@ -2510,13 +2510,13 @@ SUBROUTINE MD_PackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Int_BufSz = Int_BufSz + SIZE(InData%Attached) ! Attached Int_BufSz = Int_BufSz + SIZE(InData%Top) ! Top Int_BufSz = Int_BufSz + 1 ! nAttached - Db_BufSz = Db_BufSz + 1 ! conM - Db_BufSz = Db_BufSz + 1 ! conV - Db_BufSz = Db_BufSz + 1 ! conFX - Db_BufSz = Db_BufSz + 1 ! conFY - Db_BufSz = Db_BufSz + 1 ! conFZ - Db_BufSz = Db_BufSz + 1 ! conCa - Db_BufSz = Db_BufSz + 1 ! conCdA + Db_BufSz = Db_BufSz + 1 ! pointM + Db_BufSz = Db_BufSz + 1 ! pointV + Db_BufSz = Db_BufSz + 1 ! pointFX + Db_BufSz = Db_BufSz + 1 ! pointFY + Db_BufSz = Db_BufSz + 1 ! pointFZ + Db_BufSz = Db_BufSz + 1 ! pointCa + Db_BufSz = Db_BufSz + 1 ! pointCdA Db_BufSz = Db_BufSz + 1 ! time Db_BufSz = Db_BufSz + SIZE(InData%r) ! r Db_BufSz = Db_BufSz + SIZE(InData%rd) ! rd @@ -2576,19 +2576,19 @@ SUBROUTINE MD_PackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, END DO IntKiBuf(Int_Xferred) = InData%nAttached Int_Xferred = Int_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conM + DbKiBuf(Db_Xferred) = InData%pointM Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conV + DbKiBuf(Db_Xferred) = InData%pointV Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conFX + DbKiBuf(Db_Xferred) = InData%pointFX Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conFY + DbKiBuf(Db_Xferred) = InData%pointFY Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conFZ + DbKiBuf(Db_Xferred) = InData%pointFZ Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conCa + DbKiBuf(Db_Xferred) = InData%pointCa Db_Xferred = Db_Xferred + 1 - DbKiBuf(Db_Xferred) = InData%conCdA + DbKiBuf(Db_Xferred) = InData%pointCdA Db_Xferred = Db_Xferred + 1 DbKiBuf(Db_Xferred) = InData%time Db_Xferred = Db_Xferred + 1 @@ -2639,13 +2639,13 @@ SUBROUTINE MD_PackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Db_Xferred = Db_Xferred + 1 END DO END DO - END SUBROUTINE MD_PackConnect + END SUBROUTINE MD_PackPoint - SUBROUTINE MD_UnPackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) + SUBROUTINE MD_UnPackPoint( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) REAL(ReKi), ALLOCATABLE, INTENT(IN ) :: ReKiBuf(:) REAL(DbKi), ALLOCATABLE, INTENT(IN ) :: DbKiBuf(:) INTEGER(IntKi), ALLOCATABLE, INTENT(IN ) :: IntKiBuf(:) - TYPE(MD_Connect), INTENT(INOUT) :: OutData + TYPE(MD_Point), INTENT(INOUT) :: OutData INTEGER(IntKi), INTENT( OUT) :: ErrStat CHARACTER(*), INTENT( OUT) :: ErrMsg ! Local variables @@ -2658,7 +2658,7 @@ SUBROUTINE MD_UnPackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMs INTEGER(IntKi) :: i2, i2_l, i2_u ! bounds (upper/lower) for an array dimension 2 INTEGER(IntKi) :: ErrStat2 CHARACTER(ErrMsgLen) :: ErrMsg2 - CHARACTER(*), PARAMETER :: RoutineName = 'MD_UnPackConnect' + CHARACTER(*), PARAMETER :: RoutineName = 'MD_UnPackPoint' ! buffers to store meshes, if any REAL(ReKi), ALLOCATABLE :: Re_Buf(:) REAL(DbKi), ALLOCATABLE :: Db_Buf(:) @@ -2691,19 +2691,19 @@ SUBROUTINE MD_UnPackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMs END DO OutData%nAttached = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%conM = DbKiBuf(Db_Xferred) + OutData%pointM = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conV = DbKiBuf(Db_Xferred) + OutData%pointV = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conFX = DbKiBuf(Db_Xferred) + OutData%pointFX = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conFY = DbKiBuf(Db_Xferred) + OutData%pointFY = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conFZ = DbKiBuf(Db_Xferred) + OutData%pointFZ = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conCa = DbKiBuf(Db_Xferred) + OutData%pointCa = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 - OutData%conCdA = DbKiBuf(Db_Xferred) + OutData%pointCdA = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 OutData%time = DbKiBuf(Db_Xferred) Db_Xferred = Db_Xferred + 1 @@ -2773,7 +2773,7 @@ SUBROUTINE MD_UnPackConnect( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMs Db_Xferred = Db_Xferred + 1 END DO END DO - END SUBROUTINE MD_UnPackConnect + END SUBROUTINE MD_UnPackPoint SUBROUTINE MD_CopyRod( SrcRodData, DstRodData, CtrlCode, ErrStat, ErrMsg ) TYPE(MD_Rod), INTENT(IN) :: SrcRodData @@ -4461,8 +4461,8 @@ SUBROUTINE MD_CopyLine( SrcLineData, DstLineData, CtrlCode, ErrStat, ErrMsg ) DstLineData%ElasticMod = SrcLineData%ElasticMod DstLineData%OutFlagList = SrcLineData%OutFlagList DstLineData%CtrlChan = SrcLineData%CtrlChan - DstLineData%FairConnect = SrcLineData%FairConnect - DstLineData%AnchConnect = SrcLineData%AnchConnect + DstLineData%FairPoint = SrcLineData%FairPoint + DstLineData%AnchPoint = SrcLineData%AnchPoint DstLineData%N = SrcLineData%N DstLineData%endTypeA = SrcLineData%endTypeA DstLineData%endTypeB = SrcLineData%endTypeB @@ -5016,8 +5016,8 @@ SUBROUTINE MD_PackLine( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz Int_BufSz = Int_BufSz + 1 ! ElasticMod Int_BufSz = Int_BufSz + SIZE(InData%OutFlagList) ! OutFlagList Int_BufSz = Int_BufSz + 1 ! CtrlChan - Int_BufSz = Int_BufSz + 1 ! FairConnect - Int_BufSz = Int_BufSz + 1 ! AnchConnect + Int_BufSz = Int_BufSz + 1 ! FairPoint + Int_BufSz = Int_BufSz + 1 ! AnchPoint Int_BufSz = Int_BufSz + 1 ! N Int_BufSz = Int_BufSz + 1 ! endTypeA Int_BufSz = Int_BufSz + 1 ! endTypeB @@ -5225,9 +5225,9 @@ SUBROUTINE MD_PackLine( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz END DO IntKiBuf(Int_Xferred) = InData%CtrlChan Int_Xferred = Int_Xferred + 1 - IntKiBuf(Int_Xferred) = InData%FairConnect + IntKiBuf(Int_Xferred) = InData%FairPoint Int_Xferred = Int_Xferred + 1 - IntKiBuf(Int_Xferred) = InData%AnchConnect + IntKiBuf(Int_Xferred) = InData%AnchPoint Int_Xferred = Int_Xferred + 1 IntKiBuf(Int_Xferred) = InData%N Int_Xferred = Int_Xferred + 1 @@ -5866,9 +5866,9 @@ SUBROUTINE MD_UnPackLine( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) END DO OutData%CtrlChan = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%FairConnect = IntKiBuf(Int_Xferred) + OutData%FairPoint = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%AnchConnect = IntKiBuf(Int_Xferred) + OutData%AnchPoint = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 OutData%N = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 @@ -8383,18 +8383,18 @@ SUBROUTINE MD_CopyMisc( SrcMiscData, DstMiscData, CtrlCode, ErrStat, ErrMsg ) IF (ErrStat>=AbortErrLev) RETURN ENDDO ENDIF -IF (ALLOCATED(SrcMiscData%ConnectList)) THEN - i1_l = LBOUND(SrcMiscData%ConnectList,1) - i1_u = UBOUND(SrcMiscData%ConnectList,1) - IF (.NOT. ALLOCATED(DstMiscData%ConnectList)) THEN - ALLOCATE(DstMiscData%ConnectList(i1_l:i1_u),STAT=ErrStat2) +IF (ALLOCATED(SrcMiscData%PointList)) THEN + i1_l = LBOUND(SrcMiscData%PointList,1) + i1_u = UBOUND(SrcMiscData%PointList,1) + IF (.NOT. ALLOCATED(DstMiscData%PointList)) THEN + ALLOCATE(DstMiscData%PointList(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%ConnectList.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%PointList.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DO i1 = LBOUND(SrcMiscData%ConnectList,1), UBOUND(SrcMiscData%ConnectList,1) - CALL MD_Copyconnect( SrcMiscData%ConnectList(i1), DstMiscData%ConnectList(i1), CtrlCode, ErrStat2, ErrMsg2 ) + DO i1 = LBOUND(SrcMiscData%PointList,1), UBOUND(SrcMiscData%PointList,1) + CALL MD_Copypoint( SrcMiscData%PointList(i1), DstMiscData%PointList(i1), CtrlCode, ErrStat2, ErrMsg2 ) CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg,RoutineName) IF (ErrStat>=AbortErrLev) RETURN ENDDO @@ -8431,31 +8431,31 @@ SUBROUTINE MD_CopyMisc( SrcMiscData, DstMiscData, CtrlCode, ErrStat, ErrMsg ) IF (ErrStat>=AbortErrLev) RETURN ENDDO ENDIF -IF (ALLOCATED(SrcMiscData%FreeConIs)) THEN - i1_l = LBOUND(SrcMiscData%FreeConIs,1) - i1_u = UBOUND(SrcMiscData%FreeConIs,1) - IF (.NOT. ALLOCATED(DstMiscData%FreeConIs)) THEN - ALLOCATE(DstMiscData%FreeConIs(i1_l:i1_u),STAT=ErrStat2) +IF (ALLOCATED(SrcMiscData%FreePointIs)) THEN + i1_l = LBOUND(SrcMiscData%FreePointIs,1) + i1_u = UBOUND(SrcMiscData%FreePointIs,1) + IF (.NOT. ALLOCATED(DstMiscData%FreePointIs)) THEN + ALLOCATE(DstMiscData%FreePointIs(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%FreeConIs.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%FreePointIs.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstMiscData%FreeConIs = SrcMiscData%FreeConIs + DstMiscData%FreePointIs = SrcMiscData%FreePointIs ENDIF -IF (ALLOCATED(SrcMiscData%CpldConIs)) THEN - i1_l = LBOUND(SrcMiscData%CpldConIs,1) - i1_u = UBOUND(SrcMiscData%CpldConIs,1) - i2_l = LBOUND(SrcMiscData%CpldConIs,2) - i2_u = UBOUND(SrcMiscData%CpldConIs,2) - IF (.NOT. ALLOCATED(DstMiscData%CpldConIs)) THEN - ALLOCATE(DstMiscData%CpldConIs(i1_l:i1_u,i2_l:i2_u),STAT=ErrStat2) +IF (ALLOCATED(SrcMiscData%CpldPointIs)) THEN + i1_l = LBOUND(SrcMiscData%CpldPointIs,1) + i1_u = UBOUND(SrcMiscData%CpldPointIs,1) + i2_l = LBOUND(SrcMiscData%CpldPointIs,2) + i2_u = UBOUND(SrcMiscData%CpldPointIs,2) + IF (.NOT. ALLOCATED(DstMiscData%CpldPointIs)) THEN + ALLOCATE(DstMiscData%CpldPointIs(i1_l:i1_u,i2_l:i2_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%CpldConIs.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%CpldPointIs.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstMiscData%CpldConIs = SrcMiscData%CpldConIs + DstMiscData%CpldPointIs = SrcMiscData%CpldPointIs ENDIF IF (ALLOCATED(SrcMiscData%FreeRodIs)) THEN i1_l = LBOUND(SrcMiscData%FreeRodIs,1) @@ -8533,29 +8533,29 @@ SUBROUTINE MD_CopyMisc( SrcMiscData, DstMiscData, CtrlCode, ErrStat, ErrMsg ) END IF DstMiscData%LineStateIsN = SrcMiscData%LineStateIsN ENDIF -IF (ALLOCATED(SrcMiscData%ConStateIs1)) THEN - i1_l = LBOUND(SrcMiscData%ConStateIs1,1) - i1_u = UBOUND(SrcMiscData%ConStateIs1,1) - IF (.NOT. ALLOCATED(DstMiscData%ConStateIs1)) THEN - ALLOCATE(DstMiscData%ConStateIs1(i1_l:i1_u),STAT=ErrStat2) +IF (ALLOCATED(SrcMiscData%PointStateIs1)) THEN + i1_l = LBOUND(SrcMiscData%PointStateIs1,1) + i1_u = UBOUND(SrcMiscData%PointStateIs1,1) + IF (.NOT. ALLOCATED(DstMiscData%PointStateIs1)) THEN + ALLOCATE(DstMiscData%PointStateIs1(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%ConStateIs1.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%PointStateIs1.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstMiscData%ConStateIs1 = SrcMiscData%ConStateIs1 + DstMiscData%PointStateIs1 = SrcMiscData%PointStateIs1 ENDIF -IF (ALLOCATED(SrcMiscData%ConStateIsN)) THEN - i1_l = LBOUND(SrcMiscData%ConStateIsN,1) - i1_u = UBOUND(SrcMiscData%ConStateIsN,1) - IF (.NOT. ALLOCATED(DstMiscData%ConStateIsN)) THEN - ALLOCATE(DstMiscData%ConStateIsN(i1_l:i1_u),STAT=ErrStat2) +IF (ALLOCATED(SrcMiscData%PointStateIsN)) THEN + i1_l = LBOUND(SrcMiscData%PointStateIsN,1) + i1_u = UBOUND(SrcMiscData%PointStateIsN,1) + IF (.NOT. ALLOCATED(DstMiscData%PointStateIsN)) THEN + ALLOCATE(DstMiscData%PointStateIsN(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%ConStateIsN.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstMiscData%PointStateIsN.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstMiscData%ConStateIsN = SrcMiscData%ConStateIsN + DstMiscData%PointStateIsN = SrcMiscData%PointStateIsN ENDIF IF (ALLOCATED(SrcMiscData%RodStateIs1)) THEN i1_l = LBOUND(SrcMiscData%RodStateIs1,1) @@ -8731,12 +8731,12 @@ SUBROUTINE MD_DestroyMisc( MiscData, ErrStat, ErrMsg, DEALLOCATEpointers ) ENDDO DEALLOCATE(MiscData%RodList) ENDIF -IF (ALLOCATED(MiscData%ConnectList)) THEN -DO i1 = LBOUND(MiscData%ConnectList,1), UBOUND(MiscData%ConnectList,1) - CALL MD_Destroyconnect( MiscData%ConnectList(i1), ErrStat2, ErrMsg2, DEALLOCATEpointers_local ) +IF (ALLOCATED(MiscData%PointList)) THEN +DO i1 = LBOUND(MiscData%PointList,1), UBOUND(MiscData%PointList,1) + CALL MD_Destroypoint( MiscData%PointList(i1), ErrStat2, ErrMsg2, DEALLOCATEpointers_local ) CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName) ENDDO - DEALLOCATE(MiscData%ConnectList) + DEALLOCATE(MiscData%PointList) ENDIF IF (ALLOCATED(MiscData%LineList)) THEN DO i1 = LBOUND(MiscData%LineList,1), UBOUND(MiscData%LineList,1) @@ -8752,11 +8752,11 @@ SUBROUTINE MD_DestroyMisc( MiscData, ErrStat, ErrMsg, DEALLOCATEpointers ) ENDDO DEALLOCATE(MiscData%FailList) ENDIF -IF (ALLOCATED(MiscData%FreeConIs)) THEN - DEALLOCATE(MiscData%FreeConIs) +IF (ALLOCATED(MiscData%FreePointIs)) THEN + DEALLOCATE(MiscData%FreePointIs) ENDIF -IF (ALLOCATED(MiscData%CpldConIs)) THEN - DEALLOCATE(MiscData%CpldConIs) +IF (ALLOCATED(MiscData%CpldPointIs)) THEN + DEALLOCATE(MiscData%CpldPointIs) ENDIF IF (ALLOCATED(MiscData%FreeRodIs)) THEN DEALLOCATE(MiscData%FreeRodIs) @@ -8776,11 +8776,11 @@ SUBROUTINE MD_DestroyMisc( MiscData, ErrStat, ErrMsg, DEALLOCATEpointers ) IF (ALLOCATED(MiscData%LineStateIsN)) THEN DEALLOCATE(MiscData%LineStateIsN) ENDIF -IF (ALLOCATED(MiscData%ConStateIs1)) THEN - DEALLOCATE(MiscData%ConStateIs1) +IF (ALLOCATED(MiscData%PointStateIs1)) THEN + DEALLOCATE(MiscData%PointStateIs1) ENDIF -IF (ALLOCATED(MiscData%ConStateIsN)) THEN - DEALLOCATE(MiscData%ConStateIsN) +IF (ALLOCATED(MiscData%PointStateIsN)) THEN + DEALLOCATE(MiscData%PointStateIsN) ENDIF IF (ALLOCATED(MiscData%RodStateIs1)) THEN DEALLOCATE(MiscData%RodStateIs1) @@ -8960,24 +8960,24 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz END IF END DO END IF - Int_BufSz = Int_BufSz + 1 ! ConnectList allocated yes/no - IF ( ALLOCATED(InData%ConnectList) ) THEN - Int_BufSz = Int_BufSz + 2*1 ! ConnectList upper/lower bounds for each dimension - DO i1 = LBOUND(InData%ConnectList,1), UBOUND(InData%ConnectList,1) - Int_BufSz = Int_BufSz + 3 ! ConnectList: size of buffers for each call to pack subtype - CALL MD_Packconnect( Re_Buf, Db_Buf, Int_Buf, InData%ConnectList(i1), ErrStat2, ErrMsg2, .TRUE. ) ! ConnectList + Int_BufSz = Int_BufSz + 1 ! PointList allocated yes/no + IF ( ALLOCATED(InData%PointList) ) THEN + Int_BufSz = Int_BufSz + 2*1 ! PointList upper/lower bounds for each dimension + DO i1 = LBOUND(InData%PointList,1), UBOUND(InData%PointList,1) + Int_BufSz = Int_BufSz + 3 ! PointList: size of buffers for each call to pack subtype + CALL MD_Packpoint( Re_Buf, Db_Buf, Int_Buf, InData%PointList(i1), ErrStat2, ErrMsg2, .TRUE. ) ! PointList CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName) IF (ErrStat >= AbortErrLev) RETURN - IF(ALLOCATED(Re_Buf)) THEN ! ConnectList + IF(ALLOCATED(Re_Buf)) THEN ! PointList Re_BufSz = Re_BufSz + SIZE( Re_Buf ) DEALLOCATE(Re_Buf) END IF - IF(ALLOCATED(Db_Buf)) THEN ! ConnectList + IF(ALLOCATED(Db_Buf)) THEN ! PointList Db_BufSz = Db_BufSz + SIZE( Db_Buf ) DEALLOCATE(Db_Buf) END IF - IF(ALLOCATED(Int_Buf)) THEN ! ConnectList + IF(ALLOCATED(Int_Buf)) THEN ! PointList Int_BufSz = Int_BufSz + SIZE( Int_Buf ) DEALLOCATE(Int_Buf) END IF @@ -9029,15 +9029,15 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz END IF END DO END IF - Int_BufSz = Int_BufSz + 1 ! FreeConIs allocated yes/no - IF ( ALLOCATED(InData%FreeConIs) ) THEN - Int_BufSz = Int_BufSz + 2*1 ! FreeConIs upper/lower bounds for each dimension - Int_BufSz = Int_BufSz + SIZE(InData%FreeConIs) ! FreeConIs + Int_BufSz = Int_BufSz + 1 ! FreePointIs allocated yes/no + IF ( ALLOCATED(InData%FreePointIs) ) THEN + Int_BufSz = Int_BufSz + 2*1 ! FreePointIs upper/lower bounds for each dimension + Int_BufSz = Int_BufSz + SIZE(InData%FreePointIs) ! FreePointIs END IF - Int_BufSz = Int_BufSz + 1 ! CpldConIs allocated yes/no - IF ( ALLOCATED(InData%CpldConIs) ) THEN - Int_BufSz = Int_BufSz + 2*2 ! CpldConIs upper/lower bounds for each dimension - Int_BufSz = Int_BufSz + SIZE(InData%CpldConIs) ! CpldConIs + Int_BufSz = Int_BufSz + 1 ! CpldPointIs allocated yes/no + IF ( ALLOCATED(InData%CpldPointIs) ) THEN + Int_BufSz = Int_BufSz + 2*2 ! CpldPointIs upper/lower bounds for each dimension + Int_BufSz = Int_BufSz + SIZE(InData%CpldPointIs) ! CpldPointIs END IF Int_BufSz = Int_BufSz + 1 ! FreeRodIs allocated yes/no IF ( ALLOCATED(InData%FreeRodIs) ) THEN @@ -9069,15 +9069,15 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz Int_BufSz = Int_BufSz + 2*1 ! LineStateIsN upper/lower bounds for each dimension Int_BufSz = Int_BufSz + SIZE(InData%LineStateIsN) ! LineStateIsN END IF - Int_BufSz = Int_BufSz + 1 ! ConStateIs1 allocated yes/no - IF ( ALLOCATED(InData%ConStateIs1) ) THEN - Int_BufSz = Int_BufSz + 2*1 ! ConStateIs1 upper/lower bounds for each dimension - Int_BufSz = Int_BufSz + SIZE(InData%ConStateIs1) ! ConStateIs1 + Int_BufSz = Int_BufSz + 1 ! PointStateIs1 allocated yes/no + IF ( ALLOCATED(InData%PointStateIs1) ) THEN + Int_BufSz = Int_BufSz + 2*1 ! PointStateIs1 upper/lower bounds for each dimension + Int_BufSz = Int_BufSz + SIZE(InData%PointStateIs1) ! PointStateIs1 END IF - Int_BufSz = Int_BufSz + 1 ! ConStateIsN allocated yes/no - IF ( ALLOCATED(InData%ConStateIsN) ) THEN - Int_BufSz = Int_BufSz + 2*1 ! ConStateIsN upper/lower bounds for each dimension - Int_BufSz = Int_BufSz + SIZE(InData%ConStateIsN) ! ConStateIsN + Int_BufSz = Int_BufSz + 1 ! PointStateIsN allocated yes/no + IF ( ALLOCATED(InData%PointStateIsN) ) THEN + Int_BufSz = Int_BufSz + 2*1 ! PointStateIsN upper/lower bounds for each dimension + Int_BufSz = Int_BufSz + SIZE(InData%PointStateIsN) ! PointStateIsN END IF Int_BufSz = Int_BufSz + 1 ! RodStateIs1 allocated yes/no IF ( ALLOCATED(InData%RodStateIs1) ) THEN @@ -9382,18 +9382,18 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz ENDIF END DO END IF - IF ( .NOT. ALLOCATED(InData%ConnectList) ) THEN + IF ( .NOT. ALLOCATED(InData%PointList) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%ConnectList,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%ConnectList,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%PointList,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%PointList,1) Int_Xferred = Int_Xferred + 2 - DO i1 = LBOUND(InData%ConnectList,1), UBOUND(InData%ConnectList,1) - CALL MD_Packconnect( Re_Buf, Db_Buf, Int_Buf, InData%ConnectList(i1), ErrStat2, ErrMsg2, OnlySize ) ! ConnectList + DO i1 = LBOUND(InData%PointList,1), UBOUND(InData%PointList,1) + CALL MD_Packpoint( Re_Buf, Db_Buf, Int_Buf, InData%PointList(i1), ErrStat2, ErrMsg2, OnlySize ) ! PointList CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName) IF (ErrStat >= AbortErrLev) RETURN @@ -9505,37 +9505,37 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz ENDIF END DO END IF - IF ( .NOT. ALLOCATED(InData%FreeConIs) ) THEN + IF ( .NOT. ALLOCATED(InData%FreePointIs) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%FreeConIs,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%FreeConIs,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%FreePointIs,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%FreePointIs,1) Int_Xferred = Int_Xferred + 2 - DO i1 = LBOUND(InData%FreeConIs,1), UBOUND(InData%FreeConIs,1) - IntKiBuf(Int_Xferred) = InData%FreeConIs(i1) + DO i1 = LBOUND(InData%FreePointIs,1), UBOUND(InData%FreePointIs,1) + IntKiBuf(Int_Xferred) = InData%FreePointIs(i1) Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( .NOT. ALLOCATED(InData%CpldConIs) ) THEN + IF ( .NOT. ALLOCATED(InData%CpldPointIs) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%CpldConIs,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%CpldConIs,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%CpldPointIs,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%CpldPointIs,1) Int_Xferred = Int_Xferred + 2 - IntKiBuf( Int_Xferred ) = LBOUND(InData%CpldConIs,2) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%CpldConIs,2) + IntKiBuf( Int_Xferred ) = LBOUND(InData%CpldPointIs,2) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%CpldPointIs,2) Int_Xferred = Int_Xferred + 2 - DO i2 = LBOUND(InData%CpldConIs,2), UBOUND(InData%CpldConIs,2) - DO i1 = LBOUND(InData%CpldConIs,1), UBOUND(InData%CpldConIs,1) - IntKiBuf(Int_Xferred) = InData%CpldConIs(i1,i2) + DO i2 = LBOUND(InData%CpldPointIs,2), UBOUND(InData%CpldPointIs,2) + DO i1 = LBOUND(InData%CpldPointIs,1), UBOUND(InData%CpldPointIs,1) + IntKiBuf(Int_Xferred) = InData%CpldPointIs(i1,i2) Int_Xferred = Int_Xferred + 1 END DO END DO @@ -9640,33 +9640,33 @@ SUBROUTINE MD_PackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Siz Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( .NOT. ALLOCATED(InData%ConStateIs1) ) THEN + IF ( .NOT. ALLOCATED(InData%PointStateIs1) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%ConStateIs1,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%ConStateIs1,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%PointStateIs1,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%PointStateIs1,1) Int_Xferred = Int_Xferred + 2 - DO i1 = LBOUND(InData%ConStateIs1,1), UBOUND(InData%ConStateIs1,1) - IntKiBuf(Int_Xferred) = InData%ConStateIs1(i1) + DO i1 = LBOUND(InData%PointStateIs1,1), UBOUND(InData%PointStateIs1,1) + IntKiBuf(Int_Xferred) = InData%PointStateIs1(i1) Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( .NOT. ALLOCATED(InData%ConStateIsN) ) THEN + IF ( .NOT. ALLOCATED(InData%PointStateIsN) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%ConStateIsN,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%ConStateIsN,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%PointStateIsN,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%PointStateIsN,1) Int_Xferred = Int_Xferred + 2 - DO i1 = LBOUND(InData%ConStateIsN,1), UBOUND(InData%ConStateIsN,1) - IntKiBuf(Int_Xferred) = InData%ConStateIsN(i1) + DO i1 = LBOUND(InData%PointStateIsN,1), UBOUND(InData%PointStateIsN,1) + IntKiBuf(Int_Xferred) = InData%PointStateIsN(i1) Int_Xferred = Int_Xferred + 1 END DO END IF @@ -10174,20 +10174,20 @@ SUBROUTINE MD_UnPackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) IF(ALLOCATED(Int_Buf)) DEALLOCATE(Int_Buf) END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! ConnectList not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! PointList not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 i1_l = IntKiBuf( Int_Xferred ) i1_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%ConnectList)) DEALLOCATE(OutData%ConnectList) - ALLOCATE(OutData%ConnectList(i1_l:i1_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%PointList)) DEALLOCATE(OutData%PointList) + ALLOCATE(OutData%PointList(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%ConnectList.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%PointList.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i1 = LBOUND(OutData%ConnectList,1), UBOUND(OutData%ConnectList,1) + DO i1 = LBOUND(OutData%PointList,1), UBOUND(OutData%PointList,1) Buf_size=IntKiBuf( Int_Xferred ) Int_Xferred = Int_Xferred + 1 IF(Buf_size > 0) THEN @@ -10221,7 +10221,7 @@ SUBROUTINE MD_UnPackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) Int_Buf = IntKiBuf( Int_Xferred:Int_Xferred+Buf_size-1 ) Int_Xferred = Int_Xferred + Buf_size END IF - CALL MD_Unpackconnect( Re_Buf, Db_Buf, Int_Buf, OutData%ConnectList(i1), ErrStat2, ErrMsg2 ) ! ConnectList + CALL MD_Unpackpoint( Re_Buf, Db_Buf, Int_Buf, OutData%PointList(i1), ErrStat2, ErrMsg2 ) ! PointList CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName) IF (ErrStat >= AbortErrLev) RETURN @@ -10342,25 +10342,25 @@ SUBROUTINE MD_UnPackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) IF(ALLOCATED(Int_Buf)) DEALLOCATE(Int_Buf) END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! FreeConIs not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! FreePointIs not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 i1_l = IntKiBuf( Int_Xferred ) i1_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%FreeConIs)) DEALLOCATE(OutData%FreeConIs) - ALLOCATE(OutData%FreeConIs(i1_l:i1_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%FreePointIs)) DEALLOCATE(OutData%FreePointIs) + ALLOCATE(OutData%FreePointIs(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%FreeConIs.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%FreePointIs.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i1 = LBOUND(OutData%FreeConIs,1), UBOUND(OutData%FreeConIs,1) - OutData%FreeConIs(i1) = IntKiBuf(Int_Xferred) + DO i1 = LBOUND(OutData%FreePointIs,1), UBOUND(OutData%FreePointIs,1) + OutData%FreePointIs(i1) = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! CpldConIs not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! CpldPointIs not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 @@ -10370,15 +10370,15 @@ SUBROUTINE MD_UnPackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) i2_l = IntKiBuf( Int_Xferred ) i2_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%CpldConIs)) DEALLOCATE(OutData%CpldConIs) - ALLOCATE(OutData%CpldConIs(i1_l:i1_u,i2_l:i2_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%CpldPointIs)) DEALLOCATE(OutData%CpldPointIs) + ALLOCATE(OutData%CpldPointIs(i1_l:i1_u,i2_l:i2_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%CpldConIs.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%CpldPointIs.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i2 = LBOUND(OutData%CpldConIs,2), UBOUND(OutData%CpldConIs,2) - DO i1 = LBOUND(OutData%CpldConIs,1), UBOUND(OutData%CpldConIs,1) - OutData%CpldConIs(i1,i2) = IntKiBuf(Int_Xferred) + DO i2 = LBOUND(OutData%CpldPointIs,2), UBOUND(OutData%CpldPointIs,2) + DO i1 = LBOUND(OutData%CpldPointIs,1), UBOUND(OutData%CpldPointIs,1) + OutData%CpldPointIs(i1,i2) = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 END DO END DO @@ -10501,39 +10501,39 @@ SUBROUTINE MD_UnPackMisc( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg ) Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! ConStateIs1 not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! PointStateIs1 not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 i1_l = IntKiBuf( Int_Xferred ) i1_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%ConStateIs1)) DEALLOCATE(OutData%ConStateIs1) - ALLOCATE(OutData%ConStateIs1(i1_l:i1_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%PointStateIs1)) DEALLOCATE(OutData%PointStateIs1) + ALLOCATE(OutData%PointStateIs1(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%ConStateIs1.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%PointStateIs1.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i1 = LBOUND(OutData%ConStateIs1,1), UBOUND(OutData%ConStateIs1,1) - OutData%ConStateIs1(i1) = IntKiBuf(Int_Xferred) + DO i1 = LBOUND(OutData%PointStateIs1,1), UBOUND(OutData%PointStateIs1,1) + OutData%PointStateIs1(i1) = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! ConStateIsN not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! PointStateIsN not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 i1_l = IntKiBuf( Int_Xferred ) i1_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%ConStateIsN)) DEALLOCATE(OutData%ConStateIsN) - ALLOCATE(OutData%ConStateIsN(i1_l:i1_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%PointStateIsN)) DEALLOCATE(OutData%PointStateIsN) + ALLOCATE(OutData%PointStateIsN(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%ConStateIsN.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%PointStateIsN.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i1 = LBOUND(OutData%ConStateIsN,1), UBOUND(OutData%ConStateIsN,1) - OutData%ConStateIsN(i1) = IntKiBuf(Int_Xferred) + DO i1 = LBOUND(OutData%PointStateIsN,1), UBOUND(OutData%PointStateIsN,1) + OutData%PointStateIsN(i1) = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 END DO END IF @@ -10824,8 +10824,8 @@ SUBROUTINE MD_CopyParam( SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg ) ErrMsg = "" DstParamData%nLineTypes = SrcParamData%nLineTypes DstParamData%nRodTypes = SrcParamData%nRodTypes - DstParamData%nConnects = SrcParamData%nConnects - DstParamData%nConnectsExtra = SrcParamData%nConnectsExtra + DstParamData%nPoints = SrcParamData%nPoints + DstParamData%nPointsExtra = SrcParamData%nPointsExtra DstParamData%nBodies = SrcParamData%nBodies DstParamData%nRods = SrcParamData%nRods DstParamData%nLines = SrcParamData%nLines @@ -10833,7 +10833,7 @@ SUBROUTINE MD_CopyParam( SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg ) DstParamData%nFails = SrcParamData%nFails DstParamData%nFreeBodies = SrcParamData%nFreeBodies DstParamData%nFreeRods = SrcParamData%nFreeRods - DstParamData%nFreeCons = SrcParamData%nFreeCons + DstParamData%nFreePoints = SrcParamData%nFreePoints IF (ALLOCATED(SrcParamData%nCpldBodies)) THEN i1_l = LBOUND(SrcParamData%nCpldBodies,1) i1_u = UBOUND(SrcParamData%nCpldBodies,1) @@ -10858,17 +10858,17 @@ SUBROUTINE MD_CopyParam( SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg ) END IF DstParamData%nCpldRods = SrcParamData%nCpldRods ENDIF -IF (ALLOCATED(SrcParamData%nCpldCons)) THEN - i1_l = LBOUND(SrcParamData%nCpldCons,1) - i1_u = UBOUND(SrcParamData%nCpldCons,1) - IF (.NOT. ALLOCATED(DstParamData%nCpldCons)) THEN - ALLOCATE(DstParamData%nCpldCons(i1_l:i1_u),STAT=ErrStat2) +IF (ALLOCATED(SrcParamData%nCpldPoints)) THEN + i1_l = LBOUND(SrcParamData%nCpldPoints,1) + i1_u = UBOUND(SrcParamData%nCpldPoints,1) + IF (.NOT. ALLOCATED(DstParamData%nCpldPoints)) THEN + ALLOCATE(DstParamData%nCpldPoints(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating DstParamData%nCpldCons.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating DstParamData%nCpldPoints.', ErrStat, ErrMsg,RoutineName) RETURN END IF END IF - DstParamData%nCpldCons = SrcParamData%nCpldCons + DstParamData%nCpldPoints = SrcParamData%nCpldPoints ENDIF DstParamData%NConns = SrcParamData%NConns DstParamData%NAnchs = SrcParamData%NAnchs @@ -11227,8 +11227,8 @@ SUBROUTINE MD_DestroyParam( ParamData, ErrStat, ErrMsg, DEALLOCATEpointers ) IF (ALLOCATED(ParamData%nCpldRods)) THEN DEALLOCATE(ParamData%nCpldRods) ENDIF -IF (ALLOCATED(ParamData%nCpldCons)) THEN - DEALLOCATE(ParamData%nCpldCons) +IF (ALLOCATED(ParamData%nCpldPoints)) THEN + DEALLOCATE(ParamData%nCpldPoints) ENDIF IF (ALLOCATED(ParamData%OutParam)) THEN DO i1 = LBOUND(ParamData%OutParam,1), UBOUND(ParamData%OutParam,1) @@ -11333,8 +11333,8 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_BufSz = 0 Int_BufSz = Int_BufSz + 1 ! nLineTypes Int_BufSz = Int_BufSz + 1 ! nRodTypes - Int_BufSz = Int_BufSz + 1 ! nConnects - Int_BufSz = Int_BufSz + 1 ! nConnectsExtra + Int_BufSz = Int_BufSz + 1 ! nPoints + Int_BufSz = Int_BufSz + 1 ! nPointsExtra Int_BufSz = Int_BufSz + 1 ! nBodies Int_BufSz = Int_BufSz + 1 ! nRods Int_BufSz = Int_BufSz + 1 ! nLines @@ -11342,7 +11342,7 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_BufSz = Int_BufSz + 1 ! nFails Int_BufSz = Int_BufSz + 1 ! nFreeBodies Int_BufSz = Int_BufSz + 1 ! nFreeRods - Int_BufSz = Int_BufSz + 1 ! nFreeCons + Int_BufSz = Int_BufSz + 1 ! nFreePoints Int_BufSz = Int_BufSz + 1 ! nCpldBodies allocated yes/no IF ( ALLOCATED(InData%nCpldBodies) ) THEN Int_BufSz = Int_BufSz + 2*1 ! nCpldBodies upper/lower bounds for each dimension @@ -11353,10 +11353,10 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_BufSz = Int_BufSz + 2*1 ! nCpldRods upper/lower bounds for each dimension Int_BufSz = Int_BufSz + SIZE(InData%nCpldRods) ! nCpldRods END IF - Int_BufSz = Int_BufSz + 1 ! nCpldCons allocated yes/no - IF ( ALLOCATED(InData%nCpldCons) ) THEN - Int_BufSz = Int_BufSz + 2*1 ! nCpldCons upper/lower bounds for each dimension - Int_BufSz = Int_BufSz + SIZE(InData%nCpldCons) ! nCpldCons + Int_BufSz = Int_BufSz + 1 ! nCpldPoints allocated yes/no + IF ( ALLOCATED(InData%nCpldPoints) ) THEN + Int_BufSz = Int_BufSz + 2*1 ! nCpldPoints upper/lower bounds for each dimension + Int_BufSz = Int_BufSz + SIZE(InData%nCpldPoints) ! nCpldPoints END IF Int_BufSz = Int_BufSz + 1 ! NConns Int_BufSz = Int_BufSz + 1 ! NAnchs @@ -11542,9 +11542,9 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_Xferred = Int_Xferred + 1 IntKiBuf(Int_Xferred) = InData%nRodTypes Int_Xferred = Int_Xferred + 1 - IntKiBuf(Int_Xferred) = InData%nConnects + IntKiBuf(Int_Xferred) = InData%nPoints Int_Xferred = Int_Xferred + 1 - IntKiBuf(Int_Xferred) = InData%nConnectsExtra + IntKiBuf(Int_Xferred) = InData%nPointsExtra Int_Xferred = Int_Xferred + 1 IntKiBuf(Int_Xferred) = InData%nBodies Int_Xferred = Int_Xferred + 1 @@ -11560,7 +11560,7 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_Xferred = Int_Xferred + 1 IntKiBuf(Int_Xferred) = InData%nFreeRods Int_Xferred = Int_Xferred + 1 - IntKiBuf(Int_Xferred) = InData%nFreeCons + IntKiBuf(Int_Xferred) = InData%nFreePoints Int_Xferred = Int_Xferred + 1 IF ( .NOT. ALLOCATED(InData%nCpldBodies) ) THEN IntKiBuf( Int_Xferred ) = 0 @@ -11592,18 +11592,18 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( .NOT. ALLOCATED(InData%nCpldCons) ) THEN + IF ( .NOT. ALLOCATED(InData%nCpldPoints) ) THEN IntKiBuf( Int_Xferred ) = 0 Int_Xferred = Int_Xferred + 1 ELSE IntKiBuf( Int_Xferred ) = 1 Int_Xferred = Int_Xferred + 1 - IntKiBuf( Int_Xferred ) = LBOUND(InData%nCpldCons,1) - IntKiBuf( Int_Xferred + 1) = UBOUND(InData%nCpldCons,1) + IntKiBuf( Int_Xferred ) = LBOUND(InData%nCpldPoints,1) + IntKiBuf( Int_Xferred + 1) = UBOUND(InData%nCpldPoints,1) Int_Xferred = Int_Xferred + 2 - DO i1 = LBOUND(InData%nCpldCons,1), UBOUND(InData%nCpldCons,1) - IntKiBuf(Int_Xferred) = InData%nCpldCons(i1) + DO i1 = LBOUND(InData%nCpldPoints,1), UBOUND(InData%nCpldPoints,1) + IntKiBuf(Int_Xferred) = InData%nCpldPoints(i1) Int_Xferred = Int_Xferred + 1 END DO END IF @@ -12168,9 +12168,9 @@ SUBROUTINE MD_UnPackParam( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg Int_Xferred = Int_Xferred + 1 OutData%nRodTypes = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%nConnects = IntKiBuf(Int_Xferred) + OutData%nPoints = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%nConnectsExtra = IntKiBuf(Int_Xferred) + OutData%nPointsExtra = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 OutData%nBodies = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 @@ -12186,7 +12186,7 @@ SUBROUTINE MD_UnPackParam( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg Int_Xferred = Int_Xferred + 1 OutData%nFreeRods = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 - OutData%nFreeCons = IntKiBuf(Int_Xferred) + OutData%nFreePoints = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! nCpldBodies not allocated Int_Xferred = Int_Xferred + 1 @@ -12224,21 +12224,21 @@ SUBROUTINE MD_UnPackParam( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg Int_Xferred = Int_Xferred + 1 END DO END IF - IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! nCpldCons not allocated + IF ( IntKiBuf( Int_Xferred ) == 0 ) THEN ! nCpldPoints not allocated Int_Xferred = Int_Xferred + 1 ELSE Int_Xferred = Int_Xferred + 1 i1_l = IntKiBuf( Int_Xferred ) i1_u = IntKiBuf( Int_Xferred + 1) Int_Xferred = Int_Xferred + 2 - IF (ALLOCATED(OutData%nCpldCons)) DEALLOCATE(OutData%nCpldCons) - ALLOCATE(OutData%nCpldCons(i1_l:i1_u),STAT=ErrStat2) + IF (ALLOCATED(OutData%nCpldPoints)) DEALLOCATE(OutData%nCpldPoints) + ALLOCATE(OutData%nCpldPoints(i1_l:i1_u),STAT=ErrStat2) IF (ErrStat2 /= 0) THEN - CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%nCpldCons.', ErrStat, ErrMsg,RoutineName) + CALL SetErrStat(ErrID_Fatal, 'Error allocating OutData%nCpldPoints.', ErrStat, ErrMsg,RoutineName) RETURN END IF - DO i1 = LBOUND(OutData%nCpldCons,1), UBOUND(OutData%nCpldCons,1) - OutData%nCpldCons(i1) = IntKiBuf(Int_Xferred) + DO i1 = LBOUND(OutData%nCpldPoints,1), UBOUND(OutData%nCpldPoints,1) + OutData%nCpldPoints(i1) = IntKiBuf(Int_Xferred) Int_Xferred = Int_Xferred + 1 END DO END IF From cef6f8834db5372c5292bde7269729570c2c3897 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 5 Jul 2023 13:54:59 -0700 Subject: [PATCH 02/13] Additional update to output flags --- modules/moordyn/src/MoorDyn_IO.f90 | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/modules/moordyn/src/MoorDyn_IO.f90 b/modules/moordyn/src/MoorDyn_IO.f90 index d4b5e8a767..3e378c1ed7 100644 --- a/modules/moordyn/src/MoorDyn_IO.f90 +++ b/modules/moordyn/src/MoorDyn_IO.f90 @@ -541,11 +541,20 @@ SUBROUTINE MDIO_ProcessOutList(OutList, p, m, y, InitOut, ErrStat, ErrMsg ) READ (num2,*) nID ! node or segment ID p%OutParam(I)%NodeID = nID qVal = let3 ! quantity type string - ELSE IF (let2 == 'TENA' .OR. let2 == 'TA') THEN + ELSE IF (let2 == 'TENA' .OR. let2 == 'TA' .OR. let2(1:2) == 'NA') THEN p%OutParam(I)%NodeID = 0 + IF (let2(1:2) == 'NA') THEN + let2 = let2(3:) + END IF qVal = let2 - ELSE IF (let2 == 'TENB' .OR. let2 == 'TB') THEN + ELSE IF (let2 == 'TENB' .OR. let2 == 'TB' .OR. let2(1:2) == 'NB') THEN p%OutParam(I)%NodeID = m%LineList(p%OutParam(I)%ObjID)%N + IF (let2(1:2) == 'NB') THEN + let2 = let2(3:) + END IF + qVal = let2 + ELSE IF (num2 == ' ') THEN + p%OutParam(I)%NodeID = 0 qVal = let2 ELSE CALL DenoteInvalidOutput(p%OutParam(I)) ! flag as invalid From 5364b39e85d9cd895da6bb7e625d1443745e2b27 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 26 Jul 2023 15:40:42 -0700 Subject: [PATCH 03/13] Fixes body added mass bug, rod Aq bug, rod moment of inertia bug, and typos in comments --- modules/moordyn/src/MoorDyn_Body.f90 | 2 +- modules/moordyn/src/MoorDyn_Rod.f90 | 20 ++++++++++---------- modules/moordyn/src/MoorDyn_Types.f90 | 2 +- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/modules/moordyn/src/MoorDyn_Body.f90 b/modules/moordyn/src/MoorDyn_Body.f90 index 49b6e8c430..a0d5b17cd2 100644 --- a/modules/moordyn/src/MoorDyn_Body.f90 +++ b/modules/moordyn/src/MoorDyn_Body.f90 @@ -81,7 +81,7 @@ SUBROUTINE Body_Setup( Body, tempArray, p, ErrStat, ErrMsg) CALL TranslateMass6to6DOF(Body%rCG, Mtemp, Body%M0) ! account for potential CG offset <<< is the direction right? <<< DO J=1,3 - Body%M0(J,J) = Body%M0(J,J) + Body%BodyV*Body%BodyCa(J) ! add added mass in each direction about ref point (so only diagonals) <<< eventually expand to multi D + Body%M0(J,J) = Body%M0(J,J) + Body%BodyV*Body%BodyCa(J)* p%rhow ! add added mass in each direction about ref point (so only diagonals) <<< eventually expand to multi D END DO ! --------------- if this is an independent body (not coupled) ---------- diff --git a/modules/moordyn/src/MoorDyn_Rod.f90 b/modules/moordyn/src/MoorDyn_Rod.f90 index 0ae6d79161..aa3feb0645 100644 --- a/modules/moordyn/src/MoorDyn_Rod.f90 +++ b/modules/moordyn/src/MoorDyn_Rod.f90 @@ -481,7 +481,7 @@ SUBROUTINE Rod_GetStateDeriv(Rod, Xd, m, p) ! rate of change of unit vector components!! CHECK! <<<<< Xd(10) = - Rod%v6(6)*Rod%r6(5) + Rod%v6(5)*Rod%r6(6) ! i.e. u_dot_x = -omega_z*u_y + omega_y*u_z Xd(11) = Rod%v6(6)*Rod%r6(4) - Rod%v6(4)*Rod%r6(6) ! i.e. u_dot_y = omega_z*u_x - omega_x*u_z - Xd(12) = -Rod%v6(5)*Rod%r6(4) + Rod%v6(4)*Rod%r6(5) ! i.e. u_dot_z = -omega_y*u_x - omega_x*u_y + Xd(12) = -Rod%v6(5)*Rod%r6(4) + Rod%v6(4)*Rod%r6(5) ! i.e. u_dot_z = -omega_y*u_x + omega_x*u_y ! store accelerations in case they're useful as output Rod%a6 = acc @@ -502,7 +502,7 @@ SUBROUTINE Rod_GetStateDeriv(Rod, Xd, m, p) ! rate of change of unit vector components!! CHECK! <<<<< Xd(4) = - Rod%v6(6)*Rod%r6(5) + Rod%v6(5)*Rod%r6(6) ! i.e. u_dot_x = -omega_z*u_y + omega_y*u_z Xd(5) = Rod%v6(6)*Rod%r6(4) - Rod%v6(4)*Rod%r6(6) ! i.e. u_dot_y = omega_z*u_x - omega_x*u_z - Xd(6) = -Rod%v6(5)*Rod%r6(4) + Rod%v6(4)*Rod%r6(5) ! i.e. u_dot_z = -omega_y*u_x - omega_x*u_y + Xd(6) = -Rod%v6(5)*Rod%r6(4) + Rod%v6(4)*Rod%r6(5) ! i.e. u_dot_z = -omega_y*u_x + omega_x*u_y ! store angular accelerations in case they're useful as output Rod%a6(4:6) = acc(4:6) @@ -776,7 +776,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) ! 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 - ! transverse and axial Froude-Krylov force + ! transverse and axial fluid inertia force Rod%Ap(:,I) = VOF * p%rhoW*(1.0+Rod%Can)* v_i * ap ! Rod%Aq(:,I) = 0.0_DbKi ! p%rhoW*(1.0+Rod%Cat)* v_i * aq ! <<< just put a taper-based term here eventually? @@ -831,10 +831,10 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) ! >>> what about rotational drag?? <<< eqn will be Pi* Rod%d**4/16.0 omega_rel?^2... *0.5 * Cd... - ! Froud-Krylov force - Rod%Aq(:,I) = Rod%Aq(:,I) + VOF * p%rhoW*(1.0+Rod%CaEnd)* (2.0/3.0*Pi*Rod%d**3 /8.0) * aq + ! long-wave diffraction force + Rod%Aq(:,I) = Rod%Aq(:,I) + VOF * p%rhoW* Rod%CaEnd * (2.0/3.0*Pi*Rod%d**3 /8.0) * aq - ! dynamic pressure force + ! Froude-Krylov force Rod%Pd(:,I) = Rod%Pd(:,I) + VOF * 0.25* Pi*Rod%d*Rod%d * Rod%PDyn(I) * Rod%q ! added mass @@ -859,10 +859,10 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) ! axial drag Rod%Dq(:,I) = Rod%Dq(:,I) + VOF * 0.25* Pi*Rod%d*Rod%d * p%rhoW*Rod%CdEnd * MagVq * Vq - ! Froud-Krylov force - Rod%Aq(:,I) = Rod%Aq(:,I) + VOF * p%rhoW*(1.0+Rod%CaEnd)* (2.0/3.0*Pi*Rod%d**3 /8.0) * aq + ! long-wave diffraction force + Rod%Aq(:,I) = Rod%Aq(:,I) + VOF * p%rhoW* Rod%CaEnd * (2.0/3.0*Pi*Rod%d**3 /8.0) * aq - ! dynamic pressure force + ! Froud-Krylov force Rod%Pd(:,I) = Rod%Pd(:,I) - VOF * 0.25* Pi*Rod%d*Rod%d * Rod%PDyn(I) * Rod%q ! added mass @@ -958,7 +958,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) Imat_l = 0.0_DbKi if (Rod%N > 0) then I_l = 0.125*Rod%mass * Rod%d*Rod%d ! axial moment of inertia - I_r = Rod%mass/12 * (0.75*Rod%d*Rod%d + (Rod%UnstrLen/Rod%N)**2 ) * Rod%N ! summed radial moment of inertia for each segment individually + I_r = (Rod%mass / Rod%N) / 12 * (0.75*Rod%d*Rod%d + (Rod%UnstrLen/Rod%N)**2 ) * Rod%N ! summed radial moment of inertia for each segment individually Imat_l(1,1) = I_r ! inertia about CG in local orientations (as if Rod is vertical) Imat_l(2,2) = I_r diff --git a/modules/moordyn/src/MoorDyn_Types.f90 b/modules/moordyn/src/MoorDyn_Types.f90 index aac971f517..c59ad5d1dd 100644 --- a/modules/moordyn/src/MoorDyn_Types.f90 +++ b/modules/moordyn/src/MoorDyn_Types.f90 @@ -108,7 +108,7 @@ MODULE MoorDyn_Types ! ========= MD_Body ======= TYPE, PUBLIC :: MD_Body INTEGER(IntKi) :: IdNum !< integer identifier of this point [-] - INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=point [-] + INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=free, 1=fixed, -1=vessel [-] INTEGER(IntKi) , DIMENSION(1:30) :: AttachedC !< list of IdNums of points attached to this body [-] INTEGER(IntKi) , DIMENSION(1:30) :: AttachedR !< list of IdNums of rods attached to this body [-] INTEGER(IntKi) :: nAttachedC = 0 !< number of attached points [-] From dfe920292448dc2ec387886f4d90196f9b2648fa Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 9 Aug 2023 10:54:04 -0600 Subject: [PATCH 04/13] Correction term to moment of inertia --- modules/moordyn/src/MoorDyn_Rod.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/modules/moordyn/src/MoorDyn_Rod.f90 b/modules/moordyn/src/MoorDyn_Rod.f90 index aa3feb0645..b9ac986806 100644 --- a/modules/moordyn/src/MoorDyn_Rod.f90 +++ b/modules/moordyn/src/MoorDyn_Rod.f90 @@ -958,7 +958,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) Imat_l = 0.0_DbKi if (Rod%N > 0) then I_l = 0.125*Rod%mass * Rod%d*Rod%d ! axial moment of inertia - I_r = (Rod%mass / Rod%N) / 12 * (0.75*Rod%d*Rod%d + (Rod%UnstrLen/Rod%N)**2 ) * Rod%N ! summed radial moment of inertia for each segment individually + I_r = Rod%mass * ((Rod%d**2) / 16 - (Rod%UnstrLen**2) / (6 * Rod%N**2)); ! moment of inertia correction term for lumped mass approach Imat_l(1,1) = I_r ! inertia about CG in local orientations (as if Rod is vertical) Imat_l(2,2) = I_r From e1712c75e23fc2e7c21c611dcd005b0263c549e5 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 9 Aug 2023 16:04:20 -0600 Subject: [PATCH 05/13] Glue code fix for points convention --- glue-codes/fast-farm/src/FAST_Farm_Subs.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/glue-codes/fast-farm/src/FAST_Farm_Subs.f90 b/glue-codes/fast-farm/src/FAST_Farm_Subs.f90 index 8fa232a625..12678ae2ce 100644 --- a/glue-codes/fast-farm/src/FAST_Farm_Subs.f90 +++ b/glue-codes/fast-farm/src/FAST_Farm_Subs.f90 @@ -2006,7 +2006,7 @@ subroutine FARM_MD_Increment(t, n, farm, ErrStat, ErrMsg) ! ----- map MD load outputs to each turbine's substructure ----- (taken from U FullOpt1...) do nt = 1,farm%p%NumTurbines - if (farm%MD%p%nCpldCons(nt) > 0 ) then ! only map loads if MoorDyn has connections to this turbine (currently considering only Point connections <<< ) + if (farm%MD%p%nCpldPoints(nt) > 0 ) then ! only map loads if MoorDyn has connections to this turbine (currently considering only Point connections <<< ) ! copy the MD output mesh for this turbine into a copy mesh within the FAST instance !CALL MeshCopy ( farm%MD%y%CoupledLoads(nt), farm%FWrap(nt)%m%Turbine%MeshMapData%u_FarmMD_CoupledLoads, MESH_NEWCOPY, ErrStat2, ErrMsg2 ) From 4a3d87e6cb9beea924e0221166e421d9797f3dbf Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Fri, 18 Aug 2023 11:05:23 -0600 Subject: [PATCH 06/13] Body orentation input to deg --- modules/moordyn/src/MoorDyn_Body.f90 | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/modules/moordyn/src/MoorDyn_Body.f90 b/modules/moordyn/src/MoorDyn_Body.f90 index a0d5b17cd2..879ac52ec3 100644 --- a/modules/moordyn/src/MoorDyn_Body.f90 +++ b/modules/moordyn/src/MoorDyn_Body.f90 @@ -86,7 +86,8 @@ SUBROUTINE Body_Setup( Body, tempArray, p, ErrStat, ErrMsg) ! --------------- if this is an independent body (not coupled) ---------- ! set initial position and orientation of body from input file - Body%r6 = tempArray + Body%r6(1:3) = tempArray(1:3) + Body%r6(4:6) = tempArray(4:6) * (pi/180) ! calculate orientation matrix based on latest angles !RotMat(r6[3], r6[4], r6[5], OrMat); From 8b8cb60e91296ba28466f205536d72d2a2cb4f52 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Thu, 24 Aug 2023 19:06:26 -0400 Subject: [PATCH 07/13] Catenary same as MD-C and minor doc changes --- docs/source/user/moordyn/index.rst | 5 +- modules/moordyn/README.md | 8 +- modules/moordyn/src/MoorDyn_Line.f90 | 130 +++++++++++++++++---------- 3 files changed, 87 insertions(+), 56 deletions(-) diff --git a/docs/source/user/moordyn/index.rst b/docs/source/user/moordyn/index.rst index 52730e521a..626d67e83e 100644 --- a/docs/source/user/moordyn/index.rst +++ b/docs/source/user/moordyn/index.rst @@ -3,8 +3,9 @@ MoorDyn Users Guide ==================== -A standalone C++ version of MoorDyn is also available outside the OpenFAST -repository. The documentation for the C++ version covers the input file format +The documentation for MoorDyn is avaible `here `_. It features instructions +for the use of MoorDynF, the module in OpenFAST, and MoorDynC, the standalone C++ code. Input file formats +are described in the `inputs section <>`_. (`MoorDyn usage `_, specifically the section for V2) usage of MoorDyn at the FAST.Farm level (`MoorDyn with FAST.Farm `_), diff --git a/modules/moordyn/README.md b/modules/moordyn/README.md index 8a7aaeff08..1042d2a075 100644 --- a/modules/moordyn/README.md +++ b/modules/moordyn/README.md @@ -16,12 +16,10 @@ The Fortran implementation of MoorDyn, which has been developed following the FAST Modularization Framework, is included as a module in OpenFAST. -For the C++ implementation of MoorDyn, see http://www.matt-hall.ca/moordyn. -"MoorDyn C" can be compiled as a dynamically-linked library and features -simpler functions for easy coupling with models or scripts coded in C/C++, -Fortran, Matlab/Simulink, etc. It has recently been integrated into WEC-Sim. +For the C++ implementation of MoorDyn, see https://github.com/FloatingArrayDesign/MoorDyn. +"MoorDynC" is more adaptable to unique use cases and couplings. It can be compiled as a dynamically-linked library or wrapped for use in Python (as a module), Fortran, and Matlab. It features simpler functions for easy coupling with models or scripts coded in C/C++, Fortran, Matlab/Simulink, etc. An example of this coupling is it’s integration into WEC-Sim. -Both forms of MoorDyn feature the same underlying mooring model, use similar +Both forms of MoorDyn feature the same underlying mooring model, use the same input and output conventions, and are being updated and improved in parallel. They follow the same version numbering, with a "C" or "F" suffix for differentiation. diff --git a/modules/moordyn/src/MoorDyn_Line.f90 b/modules/moordyn/src/MoorDyn_Line.f90 index ee381bc988..3be69f7548 100644 --- a/modules/moordyn/src/MoorDyn_Line.f90 +++ b/modules/moordyn/src/MoorDyn_Line.f90 @@ -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) :: TenTol = 0.0001_DbKi + REAL(DbKi) :: Tol = 0.0001_DbKi REAL(DbKi), ALLOCATABLE :: LSNodes(:) REAL(DbKi), ALLOCATABLE :: LNodesX(:) REAL(DbKi), ALLOCATABLE :: LNodesZ(:) @@ -335,41 +335,59 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg) ! are stored in a module and thus their values are saved from CALL to ! CALL). + IF (XF == 0.0) THEN - CALL Catenary ( XF , ZF , Line%UnstrLen, LineProp%EA , & - WetWeight , SeabedCD, TenTol, (N+1) , & - LSNodes, LNodesX, LNodesZ , ErrStat2, ErrMsg2) + DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output + Line%r(1,J) = Line%r(1,0) + (Line%r(1,N) - Line%r(1,0))*REAL(J, DbKi)/REAL(N, DbKi) + Line%r(2,J) = Line%r(2,0) + (Line%r(2,N) - Line%r(2,0))*REAL(J, DbKi)/REAL(N, DbKi) + 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))//".") + + ELSE ! If the line is not vertical, solve for the catenary profile + + CALL Catenary ( XF , ZF , Line%UnstrLen, LineProp%EA , & + WetWeight , SeabedCD, Tol, (N+1) , & + LSNodes, LNodesX, LNodesZ , ErrStat2, ErrMsg2) - IF (ErrStat2 == ErrID_None) THEN ! if it worked, use it - ! Transform the positions of each node on the current line from the local - ! coordinate system of the current line to the inertial frame coordinate - ! system: + 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.' + ENDIF + + IF (ErrStat2 == ErrID_None) THEN ! if it worked, use it + ! Transform the positions of each node on the current line from the local + ! coordinate system of the current line to the inertial frame coordinate + ! system: - DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output - Line%r(1,J) = Line%r(1,0) + LNodesX(J+1)*COSPhi - Line%r(2,J) = Line%r(2,0) + LNodesX(J+1)*SINPhi - Line%r(3,J) = Line%r(3,0) + LNodesZ(J+1) - ENDDO ! J - All nodes per line where the line position and tension can be output + DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output + Line%r(1,J) = Line%r(1,0) + LNodesX(J+1)*COSPhi + Line%r(2,J) = Line%r(2,0) + LNodesX(J+1)*SINPhi + Line%r(3,J) = Line%r(3,0) + LNodesZ(J+1) + 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 - 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') - call WrScr(" Catenary solve of Line "//trim(Num2LStr(Line%IdNum))//" unsuccessful. Initializing as linear.") + ! print *, "Node positions: " -! print *, "Node positions: " + DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output + Line%r(1,J) = Line%r(1,0) + (Line%r(1,N) - Line%r(1,0))*REAL(J, DbKi)/REAL(N, DbKi) + Line%r(2,J) = Line%r(2,0) + (Line%r(2,N) - Line%r(2,0))*REAL(J, DbKi)/REAL(N, DbKi) + Line%r(3,J) = Line%r(3,0) + (Line%r(3,N) - Line%r(3,0))*REAL(J, DbKi)/REAL(N, DbKi) + + ! print*, Line%r(:,J) + ENDDO + + ! print*,"FYI line end A and B node coords are" + ! print*, Line%r(:,0) + ! print*, Line%r(:,N) + ENDIF - DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output - Line%r(1,J) = Line%r(1,0) + (Line%r(1,N) - Line%r(1,0))*REAL(J, DbKi)/REAL(N, DbKi) - Line%r(2,J) = Line%r(2,0) + (Line%r(2,N) - Line%r(2,0))*REAL(J, DbKi)/REAL(N, DbKi) - Line%r(3,J) = Line%r(3,0) + (Line%r(3,N) - Line%r(3,0))*REAL(J, DbKi)/REAL(N, DbKi) - -! print*, Line%r(:,J) - ENDDO - -! print*,"FYI line end A and B node coords are" -! print*, Line%r(:,0) -! print*, Line%r(:,N) ENDIF @@ -500,6 +518,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & INTEGER(4) :: MaxIter ! Maximum number of Newton-Raphson iterations possible before giving up (-) LOGICAL :: FirstIter ! Flag to determine whether or not this is the first time through the Newton-Raphson interation (flag) + LOGICAL :: reverseFlag ! Flag for when the anchor is above the fairlead ErrStat = ERrId_None @@ -518,9 +537,15 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & W = REAL( W_In , DbKi ) XF = REAL( XF_In , DbKi ) ZF = REAL( ZF_In , DbKi ) + IF ( ZF < 0.0 ) THEN ! .TRUE. if the fairlead has passed below its anchor + ZF = -ZF + reverseFlag = .TRUE. + CALL WrScr(' Warning from catenary: Anchor point is above the fairlead point for Line '//trim(Num2LStr(Line%IdNum))//', consider changing.') + ELSE + reverseFlag = .FALSE. + ENDIF - ! HF and VF cannot be initialized to zero when a portion of the line rests on the seabed and the anchor tension is nonzero ! Generate the initial guess values for the horizontal and vertical tensions @@ -531,9 +556,9 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & XF2 = XF*XF ZF2 = ZF*ZF - IF ( XF == 0.0_DbKi ) THEN ! .TRUE. if the current mooring line is exactly vertical - Lamda0 = 1.0D+06 - ELSEIF ( L <= SQRT( XF2 + ZF2 ) ) THEN ! .TRUE. if the current mooring line is taut + ! IF ( XF == 0.0_DbKi ) THEN ! .TRUE. if the current mooring line is exactly vertical + ! Lamda0 = 1.0D+06 + IF ( L <= SQRT( XF2 + ZF2 ) ) THEN ! .TRUE. if the current mooring line is taut Lamda0 = 0.2_DbKi ELSE ! The current mooring line must be slack and not vertical Lamda0 = SQRT( 3.0_DbKi*( ( L**2 - ZF2 )/XF2 - 1.0_DbKi ) ) @@ -549,33 +574,27 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & IF ( Tol <= EPSILON(TOL) ) THEN ! .TRUE. when the convergence tolerance is specified incorrectly ErrStat = ErrID_Warn ErrMsg = ' Convergence tolerance must be greater than zero in routine Catenary().' - return + RETURN ELSEIF ( XF < 0.0_DbKi ) THEN ! .TRUE. only when the local coordinate system is not computed correctly ErrStat = ErrID_Warn ErrMsg = ' The horizontal distance between an anchor and its'// & ' fairlead must not be less than zero in routine Catenary().' - return - - ELSEIF ( ZF < 0.0_DbKi ) THEN ! .TRUE. if the fairlead has passed below its anchor - ErrStat = ErrID_Warn - ErrMsg = " A line's fairlead is defined as below its anchor. You may need to swap a line's fairlead and anchor end nodes." - return - + RETURN ELSEIF ( L <= 0.0_DbKi ) THEN ! .TRUE. when the unstretched line length is specified incorrectly ErrStat = ErrID_Warn ErrMsg = ' Unstretched length of line must be greater than zero in routine Catenary().' - return + RETURN ELSEIF ( EA <= 0.0_DbKi ) THEN ! .TRUE. when the unstretched line length is specified incorrectly ErrStat = ErrID_Warn ErrMsg = ' Extensional stiffness of line must be greater than zero in routine Catenary().' - return + RETURN 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.' - return + RETURN ELSEIF ( W > 0.0_DbKi ) THEN ! .TRUE. when the line will sink in fluid @@ -584,9 +603,9 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & IF ( ( L >= LMax ) .AND. ( CB >= 0.0_DbKi ) ) then ! .TRUE. if the line is as long or longer than its maximum possible value with seabed interaction ErrStat = ErrID_Warn - !ErrMsg = ' Unstretched mooring line length too large. '// & - ! ' Routine Catenary() cannot solve quasi-static mooring line solution.' - return + ErrMsg = ' Unstretched mooring line length too large. '// & + ' Routine Catenary() cannot solve quasi-static mooring line solution.' + RETURN END IF ENDIF @@ -717,13 +736,13 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & DET = dXFdHF*dZFdVF - dXFdVF*dZFdHF - if ( EqualRealNos( DET, 0.0_DbKi ) ) then + IF ( EqualRealNos( DET, 0.0_DbKi ) ) THEN !bjj: there is a serious problem with the debugger here when DET = 0 ErrStat = ErrID_Warn ErrMsg = ' Iteration not convergent (DET is 0). '// & ' Routine Catenary() cannot solve quasi-static mooring line solution.' - return - endif + RETURN + ENDIF dHF = ( -dZFdVF*EXF + dXFdVF*EZF )/DET ! This is the incremental change in horizontal tension at the fairlead as predicted by Newton-Raphson @@ -937,6 +956,19 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & ENDIF + IF (reverseFlag) THEN + ! Follows process of MoorPy catenary.py + s = s( size(s):1:-1 ) + X = X( size(X):1:-1 ) + Z = Z( size(Z):1:-1 ) + Te = Te( size(Te):1:-1 ) + DO I = 1,N + s(I) = L - s(I) + X(I) = XF - X(I) + Z(I) = Z(I) - ZF + ENDDO + ZF = -ZF ! Return to orginal value + ENDIF ! The Newton-Raphson iteration is only accurate in double precision, so ! convert the output arguments back into the default precision for real From 357d82717e41af504f044e33bb0d0d0bca2151d9 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 13 Sep 2023 11:36:00 -0600 Subject: [PATCH 08/13] Cleaner line error printing --- modules/moordyn/src/MoorDyn.f90 | 28 ++++++++++++++++++---------- modules/moordyn/src/MoorDyn_Line.f90 | 10 ++++------ 2 files changed, 22 insertions(+), 16 deletions(-) diff --git a/modules/moordyn/src/MoorDyn.f90 b/modules/moordyn/src/MoorDyn.f90 index 8d89af50c7..6c69f952e7 100644 --- a/modules/moordyn/src/MoorDyn.f90 +++ b/modules/moordyn/src/MoorDyn.f90 @@ -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 @@ -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 @@ -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) @@ -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 @@ -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 @@ -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) @@ -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 diff --git a/modules/moordyn/src/MoorDyn_Line.f90 b/modules/moordyn/src/MoorDyn_Line.f90 index 3be69f7548..1eac9a89f6 100644 --- a/modules/moordyn/src/MoorDyn_Line.f90 +++ b/modules/moordyn/src/MoorDyn_Line.f90 @@ -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 @@ -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 @@ -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: " @@ -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 From 3cdf383fb6baef08088881a19cea077a2df78d71 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Mon, 18 Sep 2023 15:02:52 -0700 Subject: [PATCH 09/13] Added axial drag coefficient of 0.5 --- modules/moordyn/src/MoorDyn_Rod.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/modules/moordyn/src/MoorDyn_Rod.f90 b/modules/moordyn/src/MoorDyn_Rod.f90 index b9ac986806..dca892ffff 100644 --- a/modules/moordyn/src/MoorDyn_Rod.f90 +++ b/modules/moordyn/src/MoorDyn_Rod.f90 @@ -827,7 +827,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) Rod%Mext = Rod%Mext + (/ Mtemp*sinBeta, -Mtemp*cosBeta, 0.0_DbKi /) ! axial drag - Rod%Dq(:,I) = Rod%Dq(:,I) + VOF * 0.25* Pi*Rod%d*Rod%d * p%rhoW*Rod%CdEnd * MagVq * Vq + Rod%Dq(:,I) = Rod%Dq(:,I) + 0.5 * VOF * 0.25* Pi*Rod%d*Rod%d * p%rhoW*Rod%CdEnd * MagVq * Vq ! >>> what about rotational drag?? <<< eqn will be Pi* Rod%d**4/16.0 omega_rel?^2... *0.5 * Cd... @@ -857,7 +857,7 @@ SUBROUTINE Rod_DoRHS(Rod, m, p) Rod%Mext = Rod%Mext + (/ Mtemp*sinBeta, -Mtemp*cosBeta, 0.0_DbKi /) ! axial drag - Rod%Dq(:,I) = Rod%Dq(:,I) + VOF * 0.25* Pi*Rod%d*Rod%d * p%rhoW*Rod%CdEnd * MagVq * Vq + Rod%Dq(:,I) = Rod%Dq(:,I) + 0.5 * VOF * 0.25* Pi*Rod%d*Rod%d * p%rhoW*Rod%CdEnd * MagVq * Vq ! long-wave diffraction force Rod%Aq(:,I) = Rod%Aq(:,I) + VOF * p%rhoW* Rod%CaEnd * (2.0/3.0*Pi*Rod%d**3 /8.0) * aq From 7e52a674a474887d382593f0e9ba8260ce3bd4fe Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Tue, 19 Sep 2023 12:26:21 -0600 Subject: [PATCH 10/13] Catenary solver status message changes per conversation with Matt --- modules/moordyn/src/MoorDyn.f90 | 17 +++++++-------- modules/moordyn/src/MoorDyn_Line.f90 | 32 ++++++++++++++-------------- 2 files changed, 24 insertions(+), 25 deletions(-) diff --git a/modules/moordyn/src/MoorDyn.f90 b/modules/moordyn/src/MoorDyn.f90 index 6c69f952e7..8df3d2bb59 100644 --- a/modules/moordyn/src/MoorDyn.f90 +++ b/modules/moordyn/src/MoorDyn.f90 @@ -35,7 +35,7 @@ MODULE MoorDyn PRIVATE - TYPE(ProgDesc), PARAMETER :: MD_ProgDesc = ProgDesc( 'MoorDyn', 'v2.0.0', '2022-12-08' ) + TYPE(ProgDesc), PARAMETER :: MD_ProgDesc = ProgDesc( 'MoorDyn', 'v2.0.0', '2023-09-18' ) INTEGER(IntKi), PARAMETER :: wordy = 0 ! verbosity level. >1 = more console output @@ -164,7 +164,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er InitOut%Ver = MD_ProgDesc CALL WrScr(' This is MoorDyn v2, with significant input file changes from v1.') - CALL WrScr(' Copyright: (C) 2022 National Renewable Energy Laboratory, (C) 2019 Matt Hall') + CALL WrScr(' Copyright: (C) 2023 National Renewable Energy Laboratory, (C) 2019 Matt Hall') !--------------------------------------------------------------------------------------------- @@ -362,7 +362,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er Line = NextLine(i) END DO - else if (INDEX(Line, "CONTROL") > 0) then ! if failure conditions header + else if (INDEX(Line, "CONTROL") > 0) then ! if control conditions header IF (wordy > 1) print *, " Reading control channels: "; @@ -1972,7 +1972,6 @@ 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(' 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) @@ -2142,11 +2141,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 diff --git a/modules/moordyn/src/MoorDyn_Line.f90 b/modules/moordyn/src/MoorDyn_Line.f90 index 1eac9a89f6..a30a9ade20 100644 --- a/modules/moordyn/src/MoorDyn_Line.f90 +++ b/modules/moordyn/src/MoorDyn_Line.f90 @@ -351,12 +351,6 @@ SUBROUTINE Line_Initialize (Line, LineProp, rhoW, ErrStat, ErrMsg) WetWeight , SeabedCD, Tol, (N+1) , & LSNodes, LNodesX, LNodesZ , ErrStat2, ErrMsg2) - 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. Fairlead and anchor vertical seperation has changed. ' - ENDIF - IF (ErrStat2 == ErrID_None) THEN ! if it worked, use it ! Transform the positions of each node on the current line from the local ! coordinate system of the current line to the inertial frame coordinate @@ -369,8 +363,11 @@ 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: Line '//trim(Num2LStr(Line%IdNum))//' ') - + ! CALL SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, ' Line_Initialize: Line '//trim(Num2LStr(Line%IdNum))//' ') + CALL WrScr(' Catenary solve of Line '//trim(Num2LStr(Line%IdNum))//' unsuccessful. Initializing as linear.') + IF (wordy == 1) THEN + CALL WrScr(' Message from catenary solver: '//ErrMsg2) + ENDIF ! print *, "Node positions: " DO J = 0,N ! Loop through all nodes per line where the line position and tension can be output @@ -590,8 +587,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.' + ErrMsg = ' The weight of the line in fluid must not be zero in routine Catenary().' RETURN @@ -601,8 +597,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & IF ( ( L >= LMax ) .AND. ( CB >= 0.0_DbKi ) ) then ! .TRUE. if the line is as long or longer than its maximum possible value with seabed interaction ErrStat = ErrID_Warn - ErrMsg = ' Unstretched mooring line length too large. '// & - ' Routine Catenary() cannot solve quasi-static mooring line solution.' + ErrMsg = ' Unstretched mooring line length too large in routine Catenary().' RETURN END IF @@ -737,8 +732,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & IF ( EqualRealNos( DET, 0.0_DbKi ) ) THEN !bjj: there is a serious problem with the debugger here when DET = 0 ErrStat = ErrID_Warn - ErrMsg = ' Iteration not convergent (DET is 0). '// & - ' Routine Catenary() cannot solve quasi-static mooring line solution.' + ErrMsg = ' Iteration not convergent (DET is 0) in routine Catenary().' RETURN ENDIF @@ -793,8 +787,7 @@ SUBROUTINE Catenary ( XF_In, ZF_In, L_In , EA_In, & ELSEIF ( ( I == MaxIter ) .AND. ( .NOT. FirstIter ) ) THEN ! .TRUE. if we've iterated as much as we can take without finding a solution; Abort ErrStat = ErrID_Warn - ErrMsg = ' Iteration not convergent. '// & - ' Routine Catenary() cannot solve quasi-static mooring line solution.' + ErrMsg = ' Iteration not convergent in routine Catenary().' RETURN @@ -968,6 +961,13 @@ 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 + ! 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().' + RETURN + ENDIF + ! The Newton-Raphson iteration is only accurate in double precision, so ! convert the output arguments back into the default precision for real ! numbers: From bcedcc892130fa3585e12345167f2a156a723273 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Wed, 20 Sep 2023 16:22:19 -0600 Subject: [PATCH 11/13] Updated hyperlinks in documentation. One typo in a comment. --- docs/source/user/moordyn/index.rst | 4 ++-- modules/moordyn/src/MoorDyn_Types.f90 | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/source/user/moordyn/index.rst b/docs/source/user/moordyn/index.rst index 626d67e83e..f127d6a94f 100644 --- a/docs/source/user/moordyn/index.rst +++ b/docs/source/user/moordyn/index.rst @@ -6,8 +6,8 @@ MoorDyn Users Guide The documentation for MoorDyn is avaible `here `_. It features instructions for the use of MoorDynF, the module in OpenFAST, and MoorDynC, the standalone C++ code. Input file formats are described in the `inputs section <>`_. -(`MoorDyn usage `_, specifically the section for V2) +(`MoorDyn usage `_, specifically the section for V2) usage of MoorDyn at the FAST.Farm level -(`MoorDyn with FAST.Farm `_), +(`MoorDyn with FAST.Farm `_), and links to publications with the relevant theory. diff --git a/modules/moordyn/src/MoorDyn_Types.f90 b/modules/moordyn/src/MoorDyn_Types.f90 index c59ad5d1dd..a786b07300 100644 --- a/modules/moordyn/src/MoorDyn_Types.f90 +++ b/modules/moordyn/src/MoorDyn_Types.f90 @@ -139,7 +139,7 @@ MODULE MoorDyn_Types TYPE, PUBLIC :: MD_Point INTEGER(IntKi) :: IdNum !< integer identifier of this point [-] CHARACTER(10) :: type !< type of Point: fix, vessel, point [-] - INTEGER(IntKi) :: typeNum !< integer identifying the type. 0=fixed, 1=vessel, 2=point [-] + INTEGER(IntKi) :: typeNum !< integer identifying the type. 1=fixed, -1=vessel, 0=free [-] INTEGER(IntKi) , DIMENSION(1:10) :: Attached !< list of IdNums of lines attached to this point node [-] INTEGER(IntKi) , DIMENSION(1:10) :: Top !< list of ints specifying whether each line is attached at 1 = top/fairlead(end B), 0 = bottom/anchor(end A) [-] INTEGER(IntKi) :: nAttached = 0 !< number of attached lines [-] From afb944ab7166599f3b4c5048fcc4e00a4bd3e417 Mon Sep 17 00:00:00 2001 From: RyanDavies19 Date: Thu, 28 Sep 2023 13:00:56 -0600 Subject: [PATCH 12/13] Fixes to the catenary solver, including changing the units of line wet weight to N/m --- modules/moordyn/src/MoorDyn.f90 | 2 +- modules/moordyn/src/MoorDyn_Line.f90 | 22 +++++++++++----------- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/modules/moordyn/src/MoorDyn.f90 b/modules/moordyn/src/MoorDyn.f90 index 8df3d2bb59..d378015b22 100644 --- a/modules/moordyn/src/MoorDyn.f90 +++ b/modules/moordyn/src/MoorDyn.f90 @@ -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 diff --git a/modules/moordyn/src/MoorDyn_Line.f90 b/modules/moordyn/src/MoorDyn_Line.f90 index a30a9ade20..3235c4e738 100644 --- a/modules/moordyn/src/MoorDyn_Line.f90 +++ b/modules/moordyn/src/MoorDyn_Line.f90 @@ -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 (-) @@ -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(:) @@ -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 @@ -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 ) @@ -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 @@ -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().' From ac5291f3045aadb8400e28761ccd87083136f70e Mon Sep 17 00:00:00 2001 From: andrew-platt Date: Mon, 2 Oct 2023 15:37:41 -0600 Subject: [PATCH 13/13] MDupdates: update the regression tests --- reg_tests/r-test | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/reg_tests/r-test b/reg_tests/r-test index 091660bef2..968ec5e0b5 160000 --- a/reg_tests/r-test +++ b/reg_tests/r-test @@ -1 +1 @@ -Subproject commit 091660bef274e3057c9cb32f9a10131f0021b843 +Subproject commit 968ec5e0b5f403cd15af0ac54ec0b07c751af481