|
- module CPumps
- use CPumpsVariables
- ! use CPumps
- use CManifolds
- use CLog4
- implicit none
- public
- 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 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) * PumpsSpecification%MudPump1Stroke * 3.0d0 * PumpsSpecification%MudPump1VolumetricEfficiency / 9702.03d0
- a = dsqrt(PumpsSpecification%MudPump1OutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- PumpsSpecification%MudPump1LinerDiameter = 0.0
- else
- PumpsSpecification%MudPump1LinerDiameter = a
- endif
- call SetMudPump1LinerDiameterN(PumpsSpecification%MudPump1LinerDiameter)
- end subroutine
-
- subroutine CalcMudPump2LinerDiameter()
- use, intrinsic :: IEEE_ARITHMETIC
- implicit none
- real(8) :: a
- a = (MathPI / 4.d0) * PumpsSpecification%MudPump2Stroke * 3.0d0 * PumpsSpecification%MudPump2VolumetricEfficiency / 9702.03d0
- a = dsqrt(PumpsSpecification%MudPump2OutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- PumpsSpecification%MudPump2LinerDiameter = 0.0
- else
- PumpsSpecification%MudPump2LinerDiameter = a
- endif
- call SetMudPump2LinerDiameterN(PumpsSpecification%MudPump2LinerDiameter)
- end subroutine
-
- subroutine CalcMudPump3LinerDiameter()
- use, intrinsic :: IEEE_ARITHMETIC
- implicit none
- real(8) :: a
- a = (MathPI / 4.d0) * PumpsSpecification%CementPumpStroke * 3.0d0 * PumpsSpecification%CementPumpVolumetricEfficiency / 9702.03d0
- a = dsqrt(PumpsSpecification%CementPumpOutputBblStroke / a)
- if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then
- PumpsSpecification%CementPumpLinerDiameter = 0.0
- else
- PumpsSpecification%CementPumpLinerDiameter = a
- endif
- call SetMudPump3LinerDiameterN(PumpsSpecification%CementPumpLinerDiameter)
- end subroutine
-
-
-
- subroutine CalcPump1OutputBblStroke()
- implicit none
- PumpsSpecification%MudPump1OutputBblStroke = (MathPI / 4.d0) * (PumpsSpecification%MudPump1LinerDiameter**2) * PumpsSpecification%MudPump1Stroke * 3.0d0 * PumpsSpecification%MudPump1VolumetricEfficiency / 9702.03d0
- call SetMudPump1OutputBblStrokeN(PumpsSpecification%MudPump1OutputBblStroke)
- end subroutine
-
- subroutine CalcPump2OutputBblStroke()
- implicit none
- PumpsSpecification%MudPump2OutputBblStroke = (MathPI / 4.d0) * (PumpsSpecification%MudPump2LinerDiameter**2) * PumpsSpecification%MudPump2Stroke * 3.0d0 * PumpsSpecification%MudPump2VolumetricEfficiency / 9702.03d0
- call SetMudPump2OutputBblStrokeN(PumpsSpecification%MudPump2OutputBblStroke)
- end subroutine
-
- subroutine CalcPump3OutputBblStroke()
- implicit none
- PumpsSpecification%CementPumpOutputBblStroke = (MathPI / 4.d0) * (PumpsSpecification%CementPumpLinerDiameter**2) * PumpsSpecification%CementPumpStroke * 3.0d0 * PumpsSpecification%CementPumpVolumetricEfficiency / 9702.03d0
- call SetMudPump3OutputBblStrokeN(PumpsSpecification%CementPumpOutputBblStroke)
- end subroutine
-
- end module CPumps
|