|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260 |
- module CPumpsVariables
- use CIActionReference
- implicit none
- public
-
-
- ! Pumps Specifications
- real(8) :: MudPump1LinerDiameter
- real(8) :: MudPump1Stroke
- real(8) :: MudPump1MechanicalEfficiency
- real(8) :: MudPump1VolumetricEfficiency
- real(8) :: MudPump1Output
- real(8) :: MudPump1OutputBblStroke
- real(8) :: MudPump1Maximum
- real(8) :: MudPump1ReliefValvePressure
-
- real(8) :: MudPump2LinerDiameter
- real(8) :: MudPump2Stroke
- real(8) :: MudPump2MechanicalEfficiency
- real(8) :: MudPump2VolumetricEfficiency
- real(8) :: MudPump2Output
- real(8) :: MudPump2OutputBblStroke
- real(8) :: MudPump2Maximum
- real(8) :: MudPump2ReliefValvePressure
-
- real(8) :: CementPumpLinerDiameter
- real(8) :: CementPumpStroke
- real(8) :: CementPumpMechanicalEfficiency
- real(8) :: CementPumpVolumetricEfficiency
- real(8) :: CementPumpOutput
- real(8) :: CementPumpOutputBblStroke
- real(8) :: CementPumpMaximum
- real(8) :: CementPumpReliefValvePressure
-
- logical :: MudPump1ReliefValveIsSet
- logical :: MudPump2ReliefValveIsSet
- logical :: CementPumpReliefValveIsSet
-
- logical :: ManualPumpPower
- logical :: Valve1
- logical :: Valve2
- logical :: Valve3
- logical :: Valve4
- logical :: Valve5
-
- procedure (ActionDouble), pointer :: MudPump1LinerDiameterPtr
- procedure (ActionDouble), pointer :: MudPump2LinerDiameterPtr
- procedure (ActionDouble), pointer :: MudPump3LinerDiameterPtr
- procedure (ActionDouble), pointer :: MudPump1OutputBblStrokePtr
- procedure (ActionDouble), pointer :: MudPump2OutputBblStrokePtr
- procedure (ActionDouble), pointer :: MudPump3OutputBblStrokePtr
-
-
- real(8) :: MathPI = 3.14159265358979d0
-
- contains
-
-
- subroutine OpenPump1()
- use CManifolds
- implicit none
- call ChangeValve(16, .true.)
- end subroutine
-
- subroutine ClosePump1()
- use CManifolds
- implicit none
- call ChangeValve(16, .false.)
- end subroutine
-
- subroutine OpenPump2()
- use CManifolds
- implicit none
- call ChangeValve(17, .true.)
- end subroutine
-
- subroutine ClosePump2()
- use CManifolds
- implicit none
- call ChangeValve(17, .false.)
- end subroutine
-
-
- subroutine OpenCementPump()
- use CManifolds
- implicit none
- call ChangeValve(18, .true.)
- end subroutine
-
- subroutine CloseCementPump()
- use CManifolds
- implicit none
- call ChangeValve(18, .false.)
- end subroutine
-
-
-
-
-
-
-
-
-
- subroutine SubscribeMudPump1LinerDiameter(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump1LinerDiameter
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump1LinerDiameter' :: SubscribeMudPump1LinerDiameter
- implicit none
- procedure (ActionDouble) :: a
- MudPump1LinerDiameterPtr => a
- end subroutine
-
- subroutine SubscribeMudPump2LinerDiameter(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump2LinerDiameter
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump2LinerDiameter' :: SubscribeMudPump2LinerDiameter
- implicit none
- procedure (ActionDouble) :: a
- MudPump2LinerDiameterPtr => a
- end subroutine
-
- subroutine SubscribeMudPump3LinerDiameter(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump3LinerDiameter
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump3LinerDiameter' :: SubscribeMudPump3LinerDiameter
- implicit none
- procedure (ActionDouble) :: a
- MudPump3LinerDiameterPtr => a
- end subroutine
-
-
-
- subroutine SubscribeMudPump1OutputBblStroke(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump1OutputBblStroke
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump1OutputBblStroke' :: SubscribeMudPump1OutputBblStroke
- implicit none
- procedure (ActionDouble) :: a
- MudPump1OutputBblStrokePtr => a
- end subroutine
-
- subroutine SubscribeMudPump2OutputBblStroke(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump2OutputBblStroke
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump2OutputBblStroke' :: SubscribeMudPump2OutputBblStroke
- implicit none
- procedure (ActionDouble) :: a
- MudPump2OutputBblStrokePtr => a
- end subroutine
-
- subroutine SubscribeMudPump3OutputBblStroke(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump3OutputBblStroke
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump3OutputBblStroke' :: SubscribeMudPump3OutputBblStroke
- implicit none
- procedure (ActionDouble) :: a
- MudPump3OutputBblStrokePtr => a
- end subroutine
-
-
-
-
- subroutine SetMudPump1LinerDiameterN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump1LinerDiameterPtr)) call MudPump1LinerDiameterPtr(a)
- end subroutine
-
- subroutine SetMudPump2LinerDiameterN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump2LinerDiameterPtr)) call MudPump2LinerDiameterPtr(a)
- end subroutine
-
- subroutine SetMudPump3LinerDiameterN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump3LinerDiameterPtr)) call MudPump3LinerDiameterPtr(a)
- end subroutine
-
-
-
- subroutine SetMudPump1OutputBblStrokeN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump1OutputBblStrokePtr)) call MudPump1OutputBblStrokePtr(a)
- end subroutine
-
- subroutine SetMudPump2OutputBblStrokeN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump2OutputBblStrokePtr)) call MudPump2OutputBblStrokePtr(a)
- end subroutine
-
- subroutine SetMudPump3OutputBblStrokeN(a)
- implicit none
- real(8) :: a
- if(associated(MudPump3OutputBblStrokePtr)) call MudPump3OutputBblStrokePtr(a)
- end subroutine
-
-
-
-
- subroutine CalcMudPump1LinerDiameter()
- use, intrinsic :: IEEE_ARITHMETIC
- implicit none
- real(8) :: a
- a = (MathPI / 4.d0) * MudPump1Stroke * 3.0d0 * MudPump1VolumetricEfficiency / 9702.03d0
- a = dsqrt(MudPump1OutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- MudPump1LinerDiameter = 0.0
- else
- MudPump1LinerDiameter = a
- endif
- call SetMudPump1LinerDiameterN(MudPump1LinerDiameter)
- end subroutine
-
- subroutine CalcMudPump2LinerDiameter()
- use, intrinsic :: IEEE_ARITHMETIC
- implicit none
- real(8) :: a
- a = (MathPI / 4.d0) * MudPump2Stroke * 3.0d0 * MudPump2VolumetricEfficiency / 9702.03d0
- a = dsqrt(MudPump2OutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- MudPump2LinerDiameter = 0.0
- else
- MudPump2LinerDiameter = a
- endif
- call SetMudPump2LinerDiameterN(MudPump2LinerDiameter)
- end subroutine
-
- subroutine CalcMudPump3LinerDiameter()
- use, intrinsic :: IEEE_ARITHMETIC
- implicit none
- real(8) :: a
- a = (MathPI / 4.d0) * CementPumpStroke * 3.0d0 * CementPumpVolumetricEfficiency / 9702.03d0
- a = dsqrt(CementPumpOutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- CementPumpLinerDiameter = 0.0
- else
- CementPumpLinerDiameter = a
- endif
- call SetMudPump3LinerDiameterN(CementPumpLinerDiameter)
- end subroutine
-
-
-
- subroutine CalcPump1OutputBblStroke()
- implicit none
- MudPump1OutputBblStroke = (MathPI / 4.d0) * (MudPump1LinerDiameter**2) * MudPump1Stroke * 3.0d0 * MudPump1VolumetricEfficiency / 9702.03d0
- call SetMudPump1OutputBblStrokeN(MudPump1OutputBblStroke)
- end subroutine
-
- subroutine CalcPump2OutputBblStroke()
- implicit none
- MudPump2OutputBblStroke = (MathPI / 4.d0) * (MudPump2LinerDiameter**2) * MudPump2Stroke * 3.0d0 * MudPump2VolumetricEfficiency / 9702.03d0
- call SetMudPump2OutputBblStrokeN(MudPump2OutputBblStroke)
- end subroutine
-
- subroutine CalcPump3OutputBblStroke()
- implicit none
- CementPumpOutputBblStroke = (MathPI / 4.d0) * (CementPumpLinerDiameter**2) * CementPumpStroke * 3.0d0 * CementPumpVolumetricEfficiency / 9702.03d0
- call SetMudPump3OutputBblStrokeN(CementPumpOutputBblStroke)
- end subroutine
-
- end module CPumpsVariables
|