Skip to content

Commit

Permalink
FVW: turn off "Reevaluation" info after first occurance
Browse files Browse the repository at this point in the history
-- [INFO] FVW: Update States: reevaluation at the same starting time
  • Loading branch information
andrew-platt committed Oct 10, 2023
1 parent 5868f14 commit 0445b3d
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 1 deletion.
5 changes: 4 additions & 1 deletion modules/aerodyn/src/FVW.f90
Original file line number Diff line number Diff line change
Expand Up @@ -584,7 +584,10 @@ subroutine FVW_UpdateStates( t, n, u, utimes, p, x, xd, z, OtherState, AFInfo, m
m%ComputeWakeInduced = .FALSE.
endif
if (bReevaluation) then
call WrScr('[INFO] FVW: Update States: reevaluation at the same starting time')
if (m%InfoReEval) then
call WrScr('[INFO] FVW: Update States: reevaluation at the same starting time. This will not print on subsequent occurances.')
m%InfoReEval = .false.
endif
call RollBackPreviousTimeStep() ! Cancel wake emission done in previous call
m%ComputeWakeInduced = .TRUE.
endif
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/FVW_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -209,6 +209,7 @@ typedef ^ ^ ReKi
typedef ^ ^ ReKi Uind :: - - "Induced velocities obtained at control points" -
# Outputs
typedef ^ ^ GridOutType GridOutputs {:} - - "Number of VTK grid to output" -
typedef ^ ^ Logical InfoReeval - .true. - "Give info about Reevaluation: gets set to false after first info statement" -

# ........ Input ............
# Rotors
Expand Down
5 changes: 5 additions & 0 deletions modules/aerodyn/src/FVW_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -240,6 +240,7 @@ MODULE FVW_Types
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: CPs !< Control points used for wake rollup computation [-]
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: Uind !< Induced velocities obtained at control points [-]
TYPE(GridOutType) , DIMENSION(:), ALLOCATABLE :: GridOutputs !< Number of VTK grid to output [-]
LOGICAL :: InfoReeval = .true. !< Give info about Reevaluation: gets set to false after first info statement [-]
END TYPE FVW_MiscVarType
! =======================
! ========= Rot_InputType =======
Expand Down Expand Up @@ -3531,6 +3532,7 @@ subroutine FVW_CopyMisc(SrcMiscData, DstMiscData, CtrlCode, ErrStat, ErrMsg)
if (ErrStat >= AbortErrLev) return
end do
end if
DstMiscData%InfoReeval = SrcMiscData%InfoReeval
end subroutine

subroutine FVW_DestroyMisc(MiscData, ErrStat, ErrMsg)
Expand Down Expand Up @@ -3639,6 +3641,7 @@ subroutine FVW_PackMisc(Buf, Indata)
call FVW_PackGridOutType(Buf, InData%GridOutputs(i1))
end do
end if
call RegPack(Buf, InData%InfoReeval)
if (RegCheckErr(Buf, RoutineName)) return
end subroutine

Expand Down Expand Up @@ -3750,6 +3753,8 @@ subroutine FVW_UnPackMisc(Buf, OutData)
call FVW_UnpackGridOutType(Buf, OutData%GridOutputs(i1)) ! GridOutputs
end do
end if
call RegUnpack(Buf, OutData%InfoReeval)
if (RegCheckErr(Buf, RoutineName)) return
end subroutine

subroutine FVW_CopyRot_InputType(SrcRot_InputTypeData, DstRot_InputTypeData, CtrlCode, ErrStat, ErrMsg)
Expand Down

0 comments on commit 0445b3d

Please sign in to comment.