Skip to content

Commit

Permalink
Merge pull request #3 from bjonkman/f/FloatingLin
Browse files Browse the repository at this point in the history
Small fixes
  • Loading branch information
ghaymanNREL authored Jan 2, 2019
2 parents 371fd44 + 5ad5b84 commit 46a62eb
Show file tree
Hide file tree
Showing 5 changed files with 36 additions and 34 deletions.
30 changes: 15 additions & 15 deletions modules-local/hydrodyn/src/HydroDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2453,7 +2453,7 @@ SUBROUTINE HD_JacobianPContState( t, u, p, x, xd, z, OtherState, y, m, ErrStat,


do i=1,NN
delta = p%dx(i)

! get x_op + delta x
call HydroDyn_CopyContState( x, x_perturb, MESH_UPDATECOPY, ErrStat2, ErrMsg2 )
call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName) ! we shouldn't have any errors about allocating memory here so I'm not going to return-on-error until later
Expand Down Expand Up @@ -2562,16 +2562,16 @@ SUBROUTINE HD_JacobianPDiscState( t, u, p, x, xd, z, OtherState, y, m, ErrStat,
TYPE(HydroDyn_MiscVarType), INTENT(INOUT) :: m !< Misc/optimization variables
INTEGER(IntKi), INTENT( OUT) :: ErrStat !< Error status of the operation
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dYdxd(:,:) !< Partial derivatives of output functions
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dYdxd(:,:) !< Partial derivatives of output functions
!! (Y) with respect to the discrete
!! states (xd) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXdxd(:,:) !< Partial derivatives of continuous state
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXdxd(:,:) !< Partial derivatives of continuous state
!! functions (X) with respect to the
!! discrete states (xd) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXddxd(:,:)!< Partial derivatives of discrete state
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXddxd(:,:)!< Partial derivatives of discrete state
!! functions (Xd) with respect to the
!! discrete states (xd) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dZdxd(:,:) !< Partial derivatives of constraint state
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dZdxd(:,:) !< Partial derivatives of constraint state
!! functions (Z) with respect to the
!! discrete states (xd) [intent in to avoid deallocation]

Expand Down Expand Up @@ -2636,13 +2636,13 @@ SUBROUTINE HD_JacobianPConstrState( t, u, p, x, xd, z, OtherState, y, m, ErrStat
TYPE(HydroDyn_MiscVarType), INTENT(INOUT) :: m !< Misc/optimization variables
INTEGER(IntKi), INTENT( OUT) :: ErrStat !< Error status of the operation
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dYdz(:,:) !< Partial derivatives of output functions (Y) with respect
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dYdz(:,:) !< Partial derivatives of output functions (Y) with respect
!! to the constraint states (z) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXdz(:,:) !< Partial derivatives of continuous state functions (X) with respect
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXdz(:,:) !< Partial derivatives of continuous state functions (X) with respect
!! to the constraint states (z) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXddz(:,:) !< Partial derivatives of discrete state functions (Xd) with respect
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dXddz(:,:) !< Partial derivatives of discrete state functions (Xd) with respect
!! to the constraint states (z) [intent in to avoid deallocation]
REAL(ReKi), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dZdz(:,:) !< Partial derivatives of constraint state functions (Z) with respect
REAL(R8Ki), ALLOCATABLE, OPTIONAL, INTENT(INOUT) :: dZdz(:,:) !< Partial derivatives of constraint state functions (Z) with respect
!! to the constraint states (z) [intent in to avoid deallocation]


Expand Down Expand Up @@ -3146,17 +3146,17 @@ END SUBROUTINE HD_Perturb_u
!! Do not change this without making sure subroutine HD_init_jacobian is consistant with this routine!
SUBROUTINE HD_Perturb_x( p, n, perturb_sign, x, dx )

TYPE(HydroDyn_ParameterType) , INTENT(IN ) :: p !< parameters
TYPE(HydroDyn_ParameterType) , INTENT(IN ) :: p !< parameters
INTEGER( IntKi ) , INTENT(IN ) :: n !< number of array element to use
INTEGER( IntKi ) , INTENT(IN ) :: perturb_sign !< +1 or -1 (value to multiply perturbation by; positive or negative difference)
TYPE(HydroDyn_ContinuousStateType) , INTENT(INOUT) :: x !< perturbed ED states
TYPE(HydroDyn_ContinuousStateType) , INTENT(INOUT) :: x !< perturbed ED states
REAL( R8Ki ) , INTENT( OUT) :: dx !< amount that specific state was perturbed


! local variables
integer(intKi) :: indx


dx = p%dx(n)

if (n > p%WAMIT%SS_Exctn%N) then
indx = n - p%WAMIT%SS_Exctn%N
Expand All @@ -3173,9 +3173,9 @@ END SUBROUTINE HD_Perturb_x
!! Do not change this packing without making sure subroutine hydrodyn::HD_init_jacobian is consistant with this routine!
SUBROUTINE Compute_dY(p, y_p, y_m, delta, dY)

TYPE(HydroDyn_ParameterType) , INTENT(IN ) :: p !< parameters
TYPE(HydroDyn_OutputType) , INTENT(IN ) :: y_p !< HD outputs at \f$ u + \Delta u \f$ or \f$ x + \Delta x \f$ (p=plus)
TYPE(HydroDyn_OutputType) , INTENT(IN ) :: y_m !< HD outputs at \f$ u - \Delta u \f$ or \f$ x - \Delta x \f$ (m=minus)
TYPE(HydroDyn_ParameterType) , INTENT(IN ) :: p !< parameters
TYPE(HydroDyn_OutputType) , INTENT(IN ) :: y_p !< HD outputs at \f$ u + \Delta u \f$ or \f$ x + \Delta x \f$ (p=plus)
TYPE(HydroDyn_OutputType) , INTENT(IN ) :: y_m !< HD outputs at \f$ u - \Delta u \f$ or \f$ x - \Delta x \f$ (m=minus)
REAL(R8Ki) , INTENT(IN ) :: delta !< difference in inputs or states \f$ delta = \Delta u \f$ or \f$ delta = \Delta x \f$
REAL(R8Ki) , INTENT(INOUT) :: dY(:) !< column of dYdu or dYdx: \f$ \frac{\partial Y}{\partial u_i} = \frac{y_p - y_m}{2 \, \Delta u}\f$ or \f$ \frac{\partial Y}{\partial x_i} = \frac{y_p - y_m}{2 \, \Delta x}\f$

Expand Down
14 changes: 7 additions & 7 deletions modules-local/hydrodyn/src/HydroDyn.txt
Original file line number Diff line number Diff line change
Expand Up @@ -75,8 +75,8 @@ typedef ^ ^ CHARACTER(2
# Define outputs from the initialization routine here:
#
typedef ^ InitOutputType WAMIT_InitOutputType WAMIT - - - "Initialization output from the WAMIT module" -
typedef ^ ^ WAMIT2_InitOutputType WAMIT2 - - - "Initialization output from the WAMIT2 module" -
typedef ^ ^ Waves2_InitOutputType Waves2 - - - "Initialization output from the Waves2 module" -
typedef ^ ^ WAMIT2_InitOutputType WAMIT2 - - - "Initialization output from the WAMIT2 module" -
typedef ^ ^ Waves2_InitOutputType Waves2 - - - "Initialization output from the Waves2 module" -
typedef ^ ^ Morison_InitOutputType Morison - - - "Initialization output from the Morison module" -
typedef ^ ^ CHARACTER(10) WriteOutputHdr {:} - - "The is the list of all HD-related output channel header strings (includes all sub-module channels)" -
typedef ^ ^ CHARACTER(10) WriteOutputUnt {:} - - "The is the list of all HD-related output channel unit strings (includes all sub-module channels)" -
Expand All @@ -85,11 +85,11 @@ typedef ^ ^ ProgDesc
typedef ^ ^ ReKi WtrDens - - - "Water density" (kg/m^3)
typedef ^ ^ ReKi WtrDpth - - - "Water depth" (m)
typedef ^ ^ ReKi MSL2SWL - - - "Offset between still-water level and mean sea level" (m)
typedef ^ ^ CHARACTER(LinChanLen) LinNames_y {:} - - "Names of the outputs used in linearization" -
typedef ^ ^ CHARACTER(LinChanLen) LinNames_x {:} - - "Names of the continuous states used in linearization" -
typedef ^ ^ CHARACTER(LinChanLen) LinNames_u {:} - - "Names of the inputs used in linearization" -
typedef ^ InitOutputType INTEGER DerivOrder_x {:} - - "Integer that tells FAST/MBC3 the maximum derivative order of continuous states used in linearization" -
typedef ^ ^ LOGICAL IsLoad_u {:} - - "Flag that tells FAST if the inputs used in linearization are loads (for preconditioning matrix)" -
typedef ^ ^ CHARACTER(LinChanLen) LinNames_y {:} - - "Names of the outputs used in linearization" -
typedef ^ ^ CHARACTER(LinChanLen) LinNames_x {:} - - "Names of the continuous states used in linearization" -
typedef ^ ^ CHARACTER(LinChanLen) LinNames_u {:} - - "Names of the inputs used in linearization" -
typedef ^ InitOutputType INTEGER DerivOrder_x {:} - - "Integer that tells FAST/MBC3 the maximum derivative order of continuous states used in linearization" -
typedef ^ ^ LOGICAL IsLoad_u {:} - - "Flag that tells FAST if the inputs used in linearization are loads (for preconditioning matrix)" -


# ..... HD_ModuleMapType ....................................................................................................................
Expand Down
22 changes: 11 additions & 11 deletions modules-local/hydrodyn/src/HydroDyn_Input.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3291,39 +3291,39 @@ SUBROUTINE HydroDynInput_ProcessInitData( InitInp, ErrStat, ErrMsg )
if ( (InitInp%WAMIT%ExctnMod == 2) ) then

if ( InitInp%Waves%WaveMod == 6 ) then
call SetErrStat( ErrID_Fatal, 'Externally generated full wave-kinematics time series cannot be used with State-space wave excitations. Set WaveMod 0, 1, 1P#, 2, 3, 4, or 5.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Externally generated full wave-kinematics time series cannot be used with state-space wave excitations. Set WaveMod 0, 1, 1P#, 2, 3, 4, or 5.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%Waves%WaveDirMod /= 0 ) then
call SetErrStat( ErrID_Fatal, 'Directional spreading cannot be used with State-space wave excitations. Set WaveDirMod=0.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Directional spreading cannot be used with state-space wave excitations. Set WaveDirMod=0.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%Waves2%WvDiffQTFF ) then
call SetErrStat( ErrID_Fatal, 'Cannot use full difference-frequency 2nd-order wave kinematics with State-space wave excitations. Set WvDiffQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Cannot use full difference-frequency 2nd-order wave kinematics with state-space wave excitations. Set WvDiffQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%Waves2%WvSumQTFF ) then
call SetErrStat( ErrID_Fatal, 'Cannot use full summation-frequency 2nd-order wave kinematics with State-space wave excitations. Set WvSumQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Cannot use full summation-frequency 2nd-order wave kinematics with state-space wave excitations. Set WvSumQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%PotMod /= 1 ) then
call SetErrStat( ErrID_Fatal, 'Potential-flow model via WAMIT must be used with State-space wave excitations. Set PotMod= 1.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Potential-flow model via WAMIT must be used with state-space wave excitations. Set PotMod= 1.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%WAMIT2%MnDrift /= 0 ) then
call SetErrStat( ErrID_Fatal, 'Mean-drift 2nd-order forces cannot be used with State-space wave excitations. Set MnDrift=0.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Mean-drift 2nd-order forces cannot be used with state-space wave excitations. Set MnDrift=0.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%WAMIT2%NewmanApp /= 0 ) then
call SetErrStat( ErrID_Fatal, "Mean- and slow-drift 2nd-order forces computed with Newman's approximation cannot be used with State-space wave excitations. Set NewmanApp=0.", ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, "Mean- and slow-drift 2nd-order forces computed with Newman's approximation cannot be used with state-space wave excitations. Set NewmanApp=0.", ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%WAMIT2%DiffQTF /= 0 ) then
call SetErrStat( ErrID_Fatal, 'Full difference-frequency 2nd-order forces computed with full QTF cannot be used with State-space wave excitations. Set DiffQTF=0.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Full difference-frequency 2nd-order forces computed with full QTF cannot be used with state-space wave excitations. Set DiffQTF=0.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%WAMIT2%SumQTF /= 0 ) then
call SetErrStat( ErrID_Fatal, 'Full summation -frequency 2nd-order forces computed with full QTF cannot be used with State-space wave excitations. Set SumQTF=0.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Full summation-frequency 2nd-order forces computed with full QTF cannot be used with State-space wave excitations. Set SumQTF=0.', ErrStat, ErrMsg, RoutineName )
end if

end if
Expand All @@ -3346,7 +3346,7 @@ SUBROUTINE HydroDynInput_ProcessInitData( InitInp, ErrStat, ErrMsg )
end if

if ( InitInp%Waves2%WvSumQTFF ) then
call SetErrStat( ErrID_Fatal, 'Cannot use full summation-frequency 2nd-order wave kinematics. Set WvSumQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Cannot use full summation-frequency 2nd-order wave kinematics for linearization. Set WvSumQTF=FALSE.', ErrStat, ErrMsg, RoutineName )
end if

if ( InitInp%PotMod > 1 ) then
Expand Down Expand Up @@ -3374,7 +3374,7 @@ SUBROUTINE HydroDynInput_ProcessInitData( InitInp, ErrStat, ErrMsg )
end if

if ( InitInp%WAMIT2%SumQTF /= 0 ) then
call SetErrStat( ErrID_Fatal, 'Full summation -frequency 2nd-order forces computed with full QTF cannot be used for linearization. Set SumQTF=0.', ErrStat, ErrMsg, RoutineName )
call SetErrStat( ErrID_Fatal, 'Full summation-frequency 2nd-order forces computed with full QTF cannot be used for linearization. Set SumQTF=0.', ErrStat, ErrMsg, RoutineName )
end if

end if
Expand Down
2 changes: 2 additions & 0 deletions modules-local/hydrodyn/src/SS_Excitation.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,8 @@ SUBROUTINE SS_Exc_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, Ini
ErrStat = ErrID_None
ErrMsg = ""

u%DummyInput = 0.0_ReKi

UnSS = -1
p%N = 0

Expand Down
2 changes: 1 addition & 1 deletion modules-local/openfast-library/src/FAST_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -356,7 +356,7 @@ typedef ^ ^ DbKi InputTimes {:} - - "Array of times associated with Input Array"
typedef FAST MAP_Data MAP_ContinuousStateType x {2} - - "Continuous states"
typedef ^ ^ MAP_DiscreteStateType xd {2} - - "Discrete states"
typedef ^ ^ MAP_ConstraintStateType z {2} - - "Constraint states"
typedef ^ ^ MAP_OtherStateType OtherSt - - "Other/optimization states"
typedef ^ ^ MAP_OtherStateType OtherSt - - - "Other/optimization states"
typedef ^ ^ MAP_ParameterType p - - - "Parameters"
typedef ^ ^ MAP_InputType u - - - "System inputs"
typedef ^ ^ MAP_OutputType y - - - "System outputs"
Expand Down

0 comments on commit 46a62eb

Please sign in to comment.