|
- module CUnityOutputs
- implicit none
- type :: UnityOutputsType
- real(8) :: KellyHoseVibrationRate
- real(8) :: BlowoutFromStringPercent
- real(8) :: Pedal
- real(8) :: FlowRate
- real(8) :: RotaryRpm
- logical :: BlowoutFromString
- logical :: BlowoutFromAnnular
- logical :: FlowFromReturnLine
- real :: FlowFromKelly
- real :: FlowFromFillupHead
- logical :: FlowKellyDisconnect
- logical :: FlowPipeDisconnect
- end type UnityOutputsType
- type(UnityOutputsType):: UnityOutputs
-
- contains
-
- ! subroutine Setup()
- ! use CDataDisplayConsole
- ! use ConfigurationVariables
- ! implicit none
- ! ! PumpsSpmChanges => Calc_KellyHoseVibrationRate
- ! ! call data%Equipments%DataDisplayConsole%OnRotaryRpmChange%Add(Set_RotaryRpm)
- ! end subroutine
-
-
-
-
-
-
-
-
-
-
- subroutine Set_BlowoutFromString(v)
- implicit none
- logical, intent (in) :: v
- UnityOutputs%BlowoutFromString = v
- #ifdef deb
- print*, 'BlowoutFromString=', v
- #endif
- end subroutine
-
- logical function Get_BlowoutFromString()
- implicit none
- Get_BlowoutFromString = UnityOutputs%BlowoutFromString
- end function
-
- subroutine Set_BlowoutFromAnnular(v)
- implicit none
- logical, intent (in) :: v
- UnityOutputs%BlowoutFromAnnular = v
- #ifdef deb
- print*, 'BlowoutFromAnnular=', v
- #endif
- end subroutine
-
- logical function Get_BlowoutFromAnnular()
- implicit none
- Get_BlowoutFromAnnular = UnityOutputs%BlowoutFromAnnular
- end function
-
-
-
-
-
- subroutine Set_FlowFromReturnLine(v)
- implicit none
- logical, intent (in) :: v
- UnityOutputs%FlowFromReturnLine = v
- #ifdef deb
- print*, 'FlowFromReturnLine=', v
- #endif
- end subroutine
-
- logical function Get_FlowFromReturnLine()
- implicit none
- Get_FlowFromReturnLine = UnityOutputs%FlowFromReturnLine
- end function
-
-
-
- subroutine Set_FlowFromKelly(v)
- implicit none
- real, intent (in) :: v
- UnityOutputs%FlowFromKelly = v
- #ifdef deb
- print*, 'FlowFromKelly=', v
- #endif
- end subroutine
-
- real function Get_FlowFromKelly()
- implicit none
- Get_FlowFromKelly = UnityOutputs%FlowFromKelly
- end function
-
-
-
-
-
- subroutine Set_FlowFromFillupHead(v)
- implicit none
- real, intent (in) :: v
- UnityOutputs%FlowFromFillupHead = v
- #ifdef deb
- print*, 'FlowFromFillupHead=', v
- #endif
- end subroutine
-
- real function Get_FlowFromFillupHead()
- implicit none
- Get_FlowFromFillupHead = UnityOutputs%FlowFromFillupHead
- end function
-
-
-
-
-
-
- subroutine Set_FlowKellyDisconnect(v)
- implicit none
- logical, intent (in) :: v
- UnityOutputs%FlowKellyDisconnect = v
- #ifdef deb
- print*, 'FlowKellyDisconnect=', v
- #endif
- end subroutine
-
- logical function Get_FlowKellyDisconnect()
- implicit none
- Get_FlowKellyDisconnect = UnityOutputs%FlowKellyDisconnect
- end function
-
-
-
-
- subroutine Set_FlowPipeDisconnect(v)
- implicit none
- logical, intent (in) :: v
- UnityOutputs%FlowPipeDisconnect = v
- #ifdef deb
- print*, 'FlowPipeDisconnect=', v
- #endif
- end subroutine
-
- logical function Get_FlowPipeDisconnect()
- implicit none
- Get_FlowPipeDisconnect = UnityOutputs%FlowPipeDisconnect
- end function
-
- subroutine Set_BlowoutFromStringPercent(v)
- implicit none
- real(8), intent (in) :: v
- UnityOutputs%BlowoutFromStringPercent = v
- #ifdef deb
- print*, 'BlowoutFromStringPercent=', v
- #endif
- end subroutine
-
- real(8) function GetBlowoutFromStringPercent()
- implicit none
- GetBlowoutFromStringPercent = UnityOutputs%BlowoutFromStringPercent
- end function
-
- subroutine Calc_KellyHoseVibrationRate(spm1, spm2)
- use CScaleRange
- implicit none
- real(8), intent (in) :: spm1, spm2
- real :: total
- total = (spm1 + spm2)/2
- UnityOutputs%KellyHoseVibrationRate = ScaleRange(total, 0.0, 10.0, 0.0, 120.0)
- #ifdef deb
- print*, 'KellyHoseVibrationRate=', UnityOutputs%KellyHoseVibrationRate
- #endif
- end subroutine
-
- real(8) function GetKellyHoseVibrationRate()
- implicit none
- GetKellyHoseVibrationRate = UnityOutputs%KellyHoseVibrationRate
- end function
-
- subroutine Set_Pedal(v)
- implicit none
- real(8), intent (in) :: v
- UnityOutputs%Pedal = v
- #ifdef deb
- print*, 'Pedal=', v
- #endif
- end subroutine
-
- real(8) function GetPedal()
- implicit none
- GetPedal = UnityOutputs%Pedal
- end function
-
- subroutine Set_FlowRate(v)
- implicit none
- real(8), intent (in) :: v
- UnityOutputs%FlowRate = v
- #ifdef deb
- print*, 'FlowRate=', v
- #endif
- end subroutine
-
-
- real(8) function GetFlowRate()
- implicit none
- GetFlowRate = UnityOutputs%FlowRate
- end function
- subroutine Set_RotaryRpm(v)
- implicit none
- real(8), intent (in) :: v
- UnityOutputs%RotaryRpm = v
- #ifdef deb
- print*, 'RotaryRpm=', v
- #endif
- end subroutine
-
- real(8) function GetRotaryRpm()
- implicit none
- GetRotaryRpm = UnityOutputs%RotaryRpm
- end function
- end module CUnityOutputs
|