Skip to content

Commit

Permalink
Flag to disable MD main output file writing even if output list provi…
Browse files Browse the repository at this point in the history
…ded. Addresses OpenFAST#2565
  • Loading branch information
RyanDavies19 committed Jan 8, 2025
1 parent 1a144d1 commit 7bfdcd8
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 2 deletions.
4 changes: 4 additions & 0 deletions modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -477,6 +477,8 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
read (OptValue,*) p%inertialF
else if ( OptString == 'INERTIALF_RAMPT') then
read (OptValue,*) p%inertialF_rampT
else if ( OptString == 'OUTSWITCH') then
read (OptValue,*) p%OutSwitch
else
CALL SetErrStat( ErrID_Warn, 'Unable to interpret input '//trim(OptString)//' in OPTIONS section.', ErrStat, ErrMsg, RoutineName )
end if
Expand Down Expand Up @@ -1616,6 +1618,8 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
IF (ErrStat2 == 0) THEN
READ(Line,*,IOSTAT=ErrStat2) m%ExtLdList(l)%IdNum, tempString1, tempString2, tempString3, tempString4, tempString5

! TODO: check for repeat IdNum's

! read in object type
CALL Conv2UC(tempString1) ! convert to uppercase so that matching is not case-sensitive
CALL DecomposeString(tempString1, let1, num1, let2, num2, let3)
Expand Down
4 changes: 2 additions & 2 deletions modules/moordyn/src/MoorDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -873,7 +873,7 @@ SUBROUTINE MDIO_OpenOutput( MD_ProgDesc, p, m, InitOut, ErrStat, ErrMsg )
! Open the output file, if necessary, and write the header
!-------------------------------------------------------------------------------------------------

IF ( ALLOCATED( p%OutParam ) .AND. p%NumOuts > 0 ) THEN ! Output has been requested so let's open an output file
IF ( ALLOCATED( p%OutParam ) .AND. p%NumOuts > 0 .AND. p%OutSwitch > 0) THEN ! Output has been requested so let's open an output file

! Open the file for output
OutFileName = TRIM(p%RootName)//'.out'
Expand Down Expand Up @@ -1580,7 +1580,7 @@ SUBROUTINE MDIO_WriteOutputs( Time, p, m, y, ErrStat, ErrMsg )
end if
! What the above does is say if ((dtOut==0) || (t >= (floor((t-dtC)/dtOut) + 1.0)*dtOut)), continue to writing files

if ( p%NumOuts > 0_IntKi ) then
if ( p%NumOuts > 0_IntKi .and. p%MDUnOut > 0 ) then

! Write the output parameters to the file
Frmt = '(F10.4,'//TRIM(Int2LStr(p%NumOuts))//'(A1,ES15.7E2))' ! should evenutally use user specified format?
Expand Down
1 change: 1 addition & 0 deletions modules/moordyn/src/MoorDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -423,6 +423,7 @@ typedef ^ ^ DbKi mc -
typedef ^ ^ DbKi cv - - - "saturated damping coefficient" "(-)"
typedef ^ ^ IntKi inertialF - 0 - "Indicates MoorDyn returning inertial moments for coupled 6DOF objects. 0: no, 1: yes, 2: yes with ramp to inertialF_rampT" -
typedef ^ ^ R8Ki inertialF_rampT - 30 - "Ramp time for inertial forces" -
typedef ^ ^ IntKi OutSwitch - 1 - "Switch to disable outputs when running with full OF. 0: no MD main outfile, 1: write MD main outfile" "(-)"
# --- parameters for wave and current ---
typedef ^ ^ IntKi nxWave - - - "number of x wave grid points" -
typedef ^ ^ IntKi nyWave - - - "number of y wave grid points" -
Expand Down
4 changes: 4 additions & 0 deletions modules/moordyn/src/MoorDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -460,6 +460,7 @@ MODULE MoorDyn_Types
REAL(DbKi) :: cv = 0.0_R8Ki !< saturated damping coefficient [(-)]
INTEGER(IntKi) :: inertialF = 0 !< Indicates MoorDyn returning inertial moments for coupled 6DOF objects. 0: no, 1: yes, 2: yes with ramp to inertialF_rampT [-]
REAL(R8Ki) :: inertialF_rampT = 30 !< Ramp time for inertial forces [-]
INTEGER(IntKi) :: OutSwitch = 1 !< Switch to disable outputs when running with full OF. 0: no MD main outfile, 1: write MD main outfile [(-)]
INTEGER(IntKi) :: nxWave = 0_IntKi !< number of x wave grid points [-]
INTEGER(IntKi) :: nyWave = 0_IntKi !< number of y wave grid points [-]
INTEGER(IntKi) :: nzWave = 0_IntKi !< number of z wave grid points [-]
Expand Down Expand Up @@ -3812,6 +3813,7 @@ subroutine MD_CopyParam(SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg)
DstParamData%cv = SrcParamData%cv
DstParamData%inertialF = SrcParamData%inertialF
DstParamData%inertialF_rampT = SrcParamData%inertialF_rampT
DstParamData%OutSwitch = SrcParamData%OutSwitch
DstParamData%nxWave = SrcParamData%nxWave
DstParamData%nyWave = SrcParamData%nyWave
DstParamData%nzWave = SrcParamData%nzWave
Expand Down Expand Up @@ -4213,6 +4215,7 @@ subroutine MD_PackParam(RF, Indata)
call RegPack(RF, InData%cv)
call RegPack(RF, InData%inertialF)
call RegPack(RF, InData%inertialF_rampT)
call RegPack(RF, InData%OutSwitch)
call RegPack(RF, InData%nxWave)
call RegPack(RF, InData%nyWave)
call RegPack(RF, InData%nzWave)
Expand Down Expand Up @@ -4319,6 +4322,7 @@ subroutine MD_UnPackParam(RF, OutData)
call RegUnpack(RF, OutData%cv); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%inertialF); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%inertialF_rampT); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%OutSwitch); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%nxWave); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%nyWave); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%nzWave); if (RegCheckErr(RF, RoutineName)) return
Expand Down

0 comments on commit 7bfdcd8

Please sign in to comment.