Skip to content

Commit

Permalink
Fix FAST.Farm, revert BD changes
Browse files Browse the repository at this point in the history
  • Loading branch information
deslaughter committed Dec 30, 2024
1 parent aa3fa50 commit 05c3e4d
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 10 deletions.
8 changes: 5 additions & 3 deletions glue-codes/fast-farm/src/FAST_Farm_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,8 @@ MODULE FAST_Farm_Subs
#endif

IMPLICIT NONE

integer(IntKi), private, parameter :: iED = 1

CONTAINS

Expand Down Expand Up @@ -881,7 +883,7 @@ SUBROUTINE Farm_InitMD( farm, ErrStat, ErrMsg )
IF (farm%FWrap(nt)%m%Turbine%p_FAST%CompSub == Module_SD) then
SubstructureMotion => farm%FWrap(nt)%m%Turbine%SD%y%y3Mesh
ELSE
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y%PlatformPtMesh
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y(iED)%PlatformPtMesh
END IF

CALL MeshMapCreate( SubstructureMotion, farm%MD%Input(1)%CoupledKinematics(nt), farm%m%FWrap_2_MD(nt), ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -965,7 +967,7 @@ subroutine FARM_MD_Increment(t, n, farm, ErrStat, ErrMsg)
IF (farm%FWrap(nt)%m%Turbine%p_FAST%CompSub == Module_SD) then
SubstructureMotion => farm%FWrap(nt)%m%Turbine%SD%y%y3Mesh
ELSE
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y%PlatformPtMesh
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y(iED)%PlatformPtMesh
END IF

CALL Transfer_Point_to_Point( SubstructureMotion, farm%MD%Input(1)%CoupledKinematics(nt), farm%m%FWrap_2_MD(nt), ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -995,7 +997,7 @@ subroutine FARM_MD_Increment(t, n, farm, ErrStat, ErrMsg)
IF (farm%FWrap(nt)%m%Turbine%p_FAST%CompSub == Module_SD) then
SubstructureMotion => farm%FWrap(nt)%m%Turbine%SD%y%y3Mesh
ELSE
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y%PlatformPtMesh
SubstructureMotion => farm%FWrap(nt)%m%Turbine%ED%y(iED)%PlatformPtMesh
END IF

! mapping; Note: SubstructureLoads_Tmp_Farm contains loads from the farm-level (at a previous step); gets integrated into individual turbines inside FWrap_Increment()
Expand Down
13 changes: 6 additions & 7 deletions modules/beamdyn/src/BeamDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3139,7 +3139,6 @@ SUBROUTINE BD_DissipativeForce( nelem, p, m,fact )
ffd_t)

call Calc_Sd_Pd_Od_Qd_Gd_Xd_Yd(m%qp%E1(:,idx_qp,nelem), &
m%qp%vvv(:,idx_qp,nelem), &
m%qp%vvp(:,idx_qp,nelem), &
m%qp%betaC(:,:,idx_qp,nelem), &
ffd_t, &
Expand All @@ -3154,8 +3153,8 @@ SUBROUTINE BD_DissipativeForce( nelem, p, m,fact )
ENDIF

CONTAINS
subroutine Calc_Sd_Pd_Od_Qd_Gd_Xd_Yd(E1, vvv, vvp, betaC, ffd, Sd, Od, Qd, Gd, Xd, Yd, Pd)
REAL(BDKi), intent(in) :: E1(:), vvv(:), vvp(:), betaC(:,:), ffd(:)
subroutine Calc_Sd_Pd_Od_Qd_Gd_Xd_Yd(E1, vvp, betaC, ffd, Sd, Od, Qd, Gd, Xd, Yd, Pd)
REAL(BDKi), intent(in) :: E1(:), vvp(:), betaC(:,:), ffd(:)
REAL(BDKi), intent(out) :: Sd(:,:), Od(:,:), Qd(:,:), Gd(:,:), Xd(:,:), Yd(:,:), Pd(:,:)
REAL(BDKi) :: D11(3,3), D12(3,3), D21(3,3), D22(3,3)
REAL(BDKi) :: b11(3,3), b12(3,3)
Expand All @@ -3170,7 +3169,7 @@ subroutine Calc_Sd_Pd_Od_Qd_Gd_Xd_Yd(E1, vvv, vvp, betaC, ffd, Sd, Od, Qd, Gd, X
b11(1:3,1:3) = -MATMUL(SkewSymMat(E1),D11)
b12(1:3,1:3) = -MATMUL(SkewSymMat(E1),D12)

SS_ome = SkewSymMat(vvv(4:6))
SS_ome = SkewSymMat( m%qp%vvv(4:6,idx_qp,nelem) )

! Compute stiffness matrix Sd
Sd(1:3,1:3) = -MATMUL(D11,SS_ome)
Expand All @@ -3184,7 +3183,7 @@ subroutine Calc_Sd_Pd_Od_Qd_Gd_Xd_Yd(E1, vvv, vvp, betaC, ffd, Sd, Od, Qd, Gd, X
Pd(4:6,4:6) = -MATMUL(b12,SS_ome)

! Compute stiffness matrix Od
alpha = SkewSymMat(vvv(1:3)) - MATMUL(SS_ome,SkewSymMat(E1))
alpha = SkewSymMat(vvp(1:3)) - MATMUL(SS_ome,SkewSymMat(E1))
Od(:,1:3) = 0.0_BDKi
Od(1:3,4:6) = MATMUL(D11,alpha) - SkewSymMat(ffd(1:3))
Od(4:6,4:6) = MATMUL(D21,alpha) - SkewSymMat(ffd(4:6))
Expand Down Expand Up @@ -3214,8 +3213,8 @@ SUBROUTINE Calc_FC_FD_ffd(E1, vvv, vvp, betaC, Fc, Fd, ffd)
REAL(BDKi) :: eed(6)

! Compute strain rates
eed(1:3) = vvv(1:3) + cross_product(E1,vvv(4:6))
eed(4:6) = vvp(4:6)
eed = vvp
eed(1:3) = eed(1:3) + cross_product(E1,vvv(4:6))

! Compute dissipative force
ffd(1:6) = MATMUL(betaC(:,:),eed)
Expand Down

0 comments on commit 05c3e4d

Please sign in to comment.