Skip to content

Commit

Permalink
Merge pull request #2005 from RyanDavies19/dev
Browse files Browse the repository at this point in the history
Removes MD driver standalone option, bug fix on initialization
  • Loading branch information
andrew-platt authored Jan 25, 2024
2 parents cf0e65a + 68d162e commit 5ea42c1
Show file tree
Hide file tree
Showing 4 changed files with 41 additions and 58 deletions.
78 changes: 38 additions & 40 deletions modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -205,9 +205,6 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
CALL WrScr(' >>> MoorDyn is running in array mode <<< ')
! could make sure the size of this is right: SIZE(InitInp%FarmCoupledKinematics)
p%nTurbines = InitInp%FarmSize
else if (InitInp%FarmSize < 0) then ! Farmsize==-1 indicates standlone, run MoorDyn as a standalone code with no openfast coupling
p%Standalone = 1
p%nTurbines = 1
else ! FarmSize==0 indicates normal, FAST module mode
p%nTurbines = 1 ! if a regular FAST module mode, we treat it like a nTurbine=1 farm case
END IF
Expand Down Expand Up @@ -1868,30 +1865,35 @@ 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 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 <<<<
! Note: in MoorDyn-F v2, the points in the mesh correspond in order to
! all the coupled bodies, then rods, then points. The below code makes
! sure all coupled objects have been offset correctly by the PtfmInit
! values (initial platform pose), including if using FAST.Farm.

! rRef and OrMatRef or the position and orientation matrix of the
! coupled object relative to the platform, based on the input file.
! They are used to set the "reference" pose of each coupled mesh
! entry before the intial offsets from PtfmInit are applied.

J = 0 ! this is the counter through the mesh points for each turbine

DO l = 1,p%nCpldBodies(iTurb)
J = J + 1

rRef = m%BodyList(m%CpldBodyIs(l,iTurb))%r6 ! for now set reference position as per input file <<<

CALL MeshPositionNode(u%CoupledKinematics(iTurb), J, rRef(1:3), ErrStat2, ErrMsg2) ! defaults to identity orientation matrix
rRef = m%BodyList(m%CpldBodyIs(l,iTurb))%r6 ! set reference position as per input file
OrMatRef = ( m%RodList(m%CpldBodyIs(l,iTurb))%OrMat ) ! set reference orientation as per input file
CALL MeshPositionNode(u%CoupledKinematics(iTurb), J, rRef(1:3), ErrStat2, ErrMsg2, OrMatRef)

! set absolute initial positions in MoorDyn
IF (p%Standalone /= 1) THEN
!TODO: >>> should also maybe set reference orientation (which might make part of a couple lines down redundant) <<<
OrMat2 = MATMUL(OrMat, ( EulerConstruct( rRef(4:6)))) ! combine the Body's relative orientation with the turbine's initial orientation
u%CoupledKinematics(iTurb)%Orientation(:,:,J) = OrMat2 ! set the result as the current orientation of the body <<<

! calculate initial point relative position, adjusted due to initial platform translations
u%CoupledKinematics(iTurb)%TranslationDisp(:,J) = InitInp%PtfmInit(1:3,iTurb) - rRef(1:3)
m%BodyList(m%CpldBodyIs(l,iTurb))%r6(1:3) = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb)
m%BodyList(m%CpldBodyIs(l,iTurb))%r6(4:6) = EulerExtract(OrMat2) ! apply rotation from PtfmInit onto input file's body orientation to get its true initial orientation
ENDIF
! set absolute initial positions in MoorDyn
OrMat2 = MATMUL(OrMat, OrMatRef) ! combine the Body's relative orientation with the turbine's initial orientation
u%CoupledKinematics(iTurb)%Orientation(:,:,J) = OrMat2 ! set the result as the current orientation of the body

! calculate initial body relative position, adjusted due to initial platform translations
u%CoupledKinematics(iTurb)%TranslationDisp(1,J) = InitInp%PtfmInit(1,iTurb) + OrMat(1,1)*rRef(1) + OrMat(2,1)*rRef(2) + OrMat(3,1)*rRef(3) - rRef(1)
u%CoupledKinematics(iTurb)%TranslationDisp(2,J) = InitInp%PtfmInit(2,iTurb) + OrMat(1,2)*rRef(1) + OrMat(2,2)*rRef(2) + OrMat(3,2)*rRef(3) - rRef(2)
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)
m%BodyList(m%CpldBodyIs(l,iTurb))%r6(1:3) = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb)
m%BodyList(m%CpldBodyIs(l,iTurb))%r6(4:6) = EulerExtract(OrMat2) ! apply rotation from PtfmInit onto input file's body orientation to get its true initial orientation

CALL MeshConstructElement(u%CoupledKinematics(iTurb), ELEMENT_POINT, ErrStat2, ErrMsg2, J) ! set node as point element

Expand All @@ -1906,19 +1908,17 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
rRef = m%RodList(m%CpldRodIs(l,iTurb))%r6 ! for now set reference position as per input file <<<

! set absolute initial positions in MoorDyn
IF (p%Standalone /= 1) THEN
OrMatRef = ( m%RodList(m%CpldRodIs(l,iTurb))%OrMat ) ! for now set reference orientation as per input file <<<
CALL MeshPositionNode(u%CoupledKinematics(iTurb), J, rRef(1:3), ErrStat2, ErrMsg2, OrMatRef) ! assign the reference position and orientation
OrMat2 = MATMUL(OrMat, OrMatRef) ! combine the Rod's relative orientation with the turbine's initial orientation
u%CoupledKinematics(iTurb)%Orientation(:,:,J) = OrMat2 ! set the result as the current orientation of the rod <<<

! calculate initial point relative position, adjusted due to initial platform rotations and translations <<< could convert to array math
u%CoupledKinematics(iTurb)%TranslationDisp(1,J) = InitInp%PtfmInit(1,iTurb) + OrMat(1,1)*rRef(1) + OrMat(2,1)*rRef(2) + OrMat(3,1)*rRef(3) - rRef(1)
u%CoupledKinematics(iTurb)%TranslationDisp(2,J) = InitInp%PtfmInit(2,iTurb) + OrMat(1,2)*rRef(1) + OrMat(2,2)*rRef(2) + OrMat(3,2)*rRef(3) - rRef(2)
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)
m%RodList(m%CpldRodIs(l,iTurb))%r6(1:3) = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb)
m%RodList(m%CpldRodIs(l,iTurb))%r6(4:6) = MATMUL(OrMat2 , (/0.0, 0.0, 1.0/) ) ! apply rotation from PtfmInit onto input file's rod orientation to get its true initial orientation
ENDIF
OrMatRef = ( m%RodList(m%CpldRodIs(l,iTurb))%OrMat ) ! set reference orientation as per input file
CALL MeshPositionNode(u%CoupledKinematics(iTurb), J, rRef(1:3), ErrStat2, ErrMsg2, OrMatRef) ! assign the reference position and orientation
OrMat2 = MATMUL(OrMat, OrMatRef) ! combine the Rod's relative orientation with the turbine's initial orientation
u%CoupledKinematics(iTurb)%Orientation(:,:,J) = OrMat2 ! set the result as the current orientation of the rod <<<

! calculate initial rod relative position, adjusted due to initial platform rotations and translations <<< could convert to array math
u%CoupledKinematics(iTurb)%TranslationDisp(1,J) = InitInp%PtfmInit(1,iTurb) + OrMat(1,1)*rRef(1) + OrMat(2,1)*rRef(2) + OrMat(3,1)*rRef(3) - rRef(1)
u%CoupledKinematics(iTurb)%TranslationDisp(2,J) = InitInp%PtfmInit(2,iTurb) + OrMat(1,2)*rRef(1) + OrMat(2,2)*rRef(2) + OrMat(3,2)*rRef(3) - rRef(2)
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)
m%RodList(m%CpldRodIs(l,iTurb))%r6(1:3) = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb)
m%RodList(m%CpldRodIs(l,iTurb))%r6(4:6) = MATMUL(OrMat2 , (/0.0, 0.0, 1.0/) ) ! apply rotation from PtfmInit onto input file's rod orientation to get its true initial orientation

! >>> still need to set Rod initial orientations accounting for PtfmInit rotation <<<

Expand All @@ -1935,14 +1935,12 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
rRef(1:3) = m%PointList(m%CpldPointIs(l,iTurb))%r

! set absolute initial positions in MoorDyn
IF (p%Standalone /= 1) THEN
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
u%CoupledKinematics(iTurb)%TranslationDisp(1,J) = InitInp%PtfmInit(1,iTurb) + OrMat(1,1)*rRef(1) + OrMat(2,1)*rRef(2) + OrMat(3,1)*rRef(3) - rRef(1)
u%CoupledKinematics(iTurb)%TranslationDisp(2,J) = InitInp%PtfmInit(2,iTurb) + OrMat(1,2)*rRef(1) + OrMat(2,2)*rRef(2) + OrMat(3,2)*rRef(3) - rRef(2)
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)
m%PointList(m%CpldPointIs(l,iTurb))%r = u%CoupledKinematics(iTurb)%Position(:,J) + u%CoupledKinematics(iTurb)%TranslationDisp(:,J) + p%TurbineRefPos(:,iTurb)
ENDIF
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
u%CoupledKinematics(iTurb)%TranslationDisp(1,J) = InitInp%PtfmInit(1,iTurb) + OrMat(1,1)*rRef(1) + OrMat(2,1)*rRef(2) + OrMat(3,1)*rRef(3) - rRef(1)
u%CoupledKinematics(iTurb)%TranslationDisp(2,J) = InitInp%PtfmInit(2,iTurb) + OrMat(1,2)*rRef(1) + OrMat(2,2)*rRef(2) + OrMat(3,2)*rRef(3) - rRef(2)
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)
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:
Expand Down
9 changes: 1 addition & 8 deletions modules/moordyn/src/MoorDyn_Driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -175,7 +175,7 @@ PROGRAM MoorDyn_Driver

if (drvrInitInp%FarmSize > 0) then ! Check if this MoorDyn instance is being run from FAST.Farm (indicated by FarmSize > 0)
nTurbines = drvrInitInp%FarmSize
else ! FarmSize==0 indicates normal, FAST module mode; FarmSize<0 indicates standalone mode
else ! FarmSize==0 indicates normal, FAST module mode
nTurbines = 1 ! if a regular FAST module mode, we treat it like a nTurbine=1 farm case
end if

Expand Down Expand Up @@ -491,10 +491,6 @@ PROGRAM MoorDyn_Driver
K = 1 ! the index of the coupling points in the input mesh CoupledKinematics
J = 1 ! the starting index of the relevant DOFs in the input array

IF (MD_InitInp%FarmSize < 0) THEN
MD_p%TurbineRefPos(:,iTurb) = 0.0
ENDIF

! any coupled bodies (type -1)
DO l = 1,MD_p%nCpldBodies(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)
Expand Down Expand Up @@ -582,9 +578,6 @@ PROGRAM MoorDyn_Driver

K = 1 ! the index of the coupling points in the input mesh CoupledKinematics
J = 1 ! the starting index of the relevant DOFs in the input array
IF (MD_InitInp%FarmSize < 0) THEN
MD_p%TurbineRefPos(:,iTurb) = 0.0
ENDIF

! any coupled bodies (type -1)
DO l = 1,MD_p%nCpldBodies(iTurb)
Expand Down
3 changes: 1 addition & 2 deletions modules/moordyn/src/MoorDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ typedef MoorDyn/MD InitInputType ReKi g - -99
typedef ^ ^ ReKi rhoW - -999.9 - "sea density" "[kg/m^3]"
typedef ^ ^ ReKi WtrDepth - -999.9 - "depth of water" "[m]"
typedef ^ ^ ReKi PtfmInit {:}{:} - - "initial position of platform(s) shape: 6, nTurbines" -
typedef ^ ^ IntKi FarmSize - 0 - "Indicates normal FAST module mode if 0, FAST.Farm coupled mode and =nTurbines if >0, standalone mode if -1" -
typedef ^ ^ IntKi FarmSize - 0 - "Indicates normal FAST module mode if 0, FAST.Farm coupled mode and =nTurbines if >0" -
typedef ^ ^ ReKi TurbineRefPos {:}{:} - - "reference position of turbines in farm, shape: 3, nTurbines" -
typedef ^ ^ ReKi Tmax - - - "simulation duration" "[s]"
typedef ^ ^ CHARACTER(1024) FileName - "" - "MoorDyn input file"
Expand Down Expand Up @@ -390,7 +390,6 @@ typedef ^ ^ DbKi mu_kT -
typedef ^ ^ DbKi mu_kA - - - "axial kinetic friction coefficient" "(-)"
typedef ^ ^ DbKi mc - - - "ratio of the static friction coefficient to the kinetic friction coefficient" "(-)"
typedef ^ ^ DbKi cv - - - "saturated damping coefficient" "(-)"
typedef ^ ^ IntKi Standalone - - - "Indicates MoorDyn run as standalone code if 1, coupled if 0" -
typedef ^ ^ IntKi inertialF - 0 - "Indicates MoorDyn returning inertial moments for coupled 6DOF objects. 1 if yes, 0 if no" -
# --- parameters for wave and current ---
typedef ^ ^ IntKi nxWave - - - "number of x wave grid points" -
Expand Down
9 changes: 1 addition & 8 deletions modules/moordyn/src/MoorDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ MODULE MoorDyn_Types
REAL(ReKi) :: rhoW = -999.9 !< sea density [[kg/m^3]]
REAL(ReKi) :: WtrDepth = -999.9 !< depth of water [[m]]
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: PtfmInit !< initial position of platform(s) shape: 6, nTurbines [-]
INTEGER(IntKi) :: FarmSize = 0 !< Indicates normal FAST module mode if 0, FAST.Farm coupled mode and =nTurbines if >0, standalone mode if -1 [-]
INTEGER(IntKi) :: FarmSize = 0 !< Indicates normal FAST module mode if 0, FAST.Farm coupled mode and =nTurbines if >0 [-]
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: TurbineRefPos !< reference position of turbines in farm, shape: 3, nTurbines [-]
REAL(ReKi) :: Tmax !< simulation duration [[s]]
CHARACTER(1024) :: FileName !< MoorDyn input file [-]
Expand Down Expand Up @@ -425,7 +425,6 @@ MODULE MoorDyn_Types
REAL(DbKi) :: mu_kA !< axial kinetic friction coefficient [(-)]
REAL(DbKi) :: mc !< ratio of the static friction coefficient to the kinetic friction coefficient [(-)]
REAL(DbKi) :: cv !< saturated damping coefficient [(-)]
INTEGER(IntKi) :: Standalone !< Indicates MoorDyn run as standalone code if 1, coupled if 0 [-]
INTEGER(IntKi) :: inertialF = 0 !< Indicates MoorDyn returning inertial moments for coupled 6DOF objects. 1 if yes, 0 if no [-]
INTEGER(IntKi) :: nxWave !< number of x wave grid points [-]
INTEGER(IntKi) :: nyWave !< number of y wave grid points [-]
Expand Down Expand Up @@ -10787,7 +10786,6 @@ SUBROUTINE MD_CopyParam( SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg )
DstParamData%mu_kA = SrcParamData%mu_kA
DstParamData%mc = SrcParamData%mc
DstParamData%cv = SrcParamData%cv
DstParamData%Standalone = SrcParamData%Standalone
DstParamData%inertialF = SrcParamData%inertialF
DstParamData%nxWave = SrcParamData%nxWave
DstParamData%nyWave = SrcParamData%nyWave
Expand Down Expand Up @@ -11300,7 +11298,6 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si
Db_BufSz = Db_BufSz + 1 ! mu_kA
Db_BufSz = Db_BufSz + 1 ! mc
Db_BufSz = Db_BufSz + 1 ! cv
Int_BufSz = Int_BufSz + 1 ! Standalone
Int_BufSz = Int_BufSz + 1 ! inertialF
Int_BufSz = Int_BufSz + 1 ! nxWave
Int_BufSz = Int_BufSz + 1 ! nyWave
Expand Down Expand Up @@ -11638,8 +11635,6 @@ SUBROUTINE MD_PackParam( ReKiBuf, DbKiBuf, IntKiBuf, Indata, ErrStat, ErrMsg, Si
Db_Xferred = Db_Xferred + 1
DbKiBuf(Db_Xferred) = InData%cv
Db_Xferred = Db_Xferred + 1
IntKiBuf(Int_Xferred) = InData%Standalone
Int_Xferred = Int_Xferred + 1
IntKiBuf(Int_Xferred) = InData%inertialF
Int_Xferred = Int_Xferred + 1
IntKiBuf(Int_Xferred) = InData%nxWave
Expand Down Expand Up @@ -12338,8 +12333,6 @@ SUBROUTINE MD_UnPackParam( ReKiBuf, DbKiBuf, IntKiBuf, Outdata, ErrStat, ErrMsg
Db_Xferred = Db_Xferred + 1
OutData%cv = DbKiBuf(Db_Xferred)
Db_Xferred = Db_Xferred + 1
OutData%Standalone = IntKiBuf(Int_Xferred)
Int_Xferred = Int_Xferred + 1
OutData%inertialF = IntKiBuf(Int_Xferred)
Int_Xferred = Int_Xferred + 1
OutData%nxWave = IntKiBuf(Int_Xferred)
Expand Down

0 comments on commit 5ea42c1

Please sign in to comment.