You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
|
- subroutine Pump3_OnMode_Solver
-
- use Pump_VARIABLES
- use CPumpsVariables
- use CDrillingConsoleVariables
- use CDataDisplayConsoleVariables
- use CSimulationVariables
- use CDrillWatchVariables
- use equipments_PowerLimit
- use CSounds
- use CWarningsVariables
-
-
- IMPLICIT NONE
- INTEGER :: Pump_No
-
-
-
- Call Pump_INPUTS
-
- !! Torque unit = (in.lbf)
- !PUMP(Pump_No)%Torque = (63025./132000.)*(1./PUMP(Pump_No)%Trans_Ratio)*(PUMP(Pump_No)%Piston_Area*PUMP(Pump_No)%Stroke_Length*PUMP(Pump_No)%StandPipe_Pressure/PUMP(Pump_No)%Mech_Efficiency/PUMP(Pump_No)%Vol_Efficiency)
-
-
-
-
-
- PUMP(3)%Speed = PUMP(3)%N_ref !Speed [RPM]
-
- if ( Pump3Failure == .true. ) then
- PUMP(3)%Speed = 0.d0
- PUMP(3)%w = 0.d0
- PUMP(3)%w_new = 0.d0
- PUMP(3)%w_old = 0.d0
- end if
-
- Call Pump_Solver(3)
- Call Pump_Total_Counts
-
- Call Set_MP1SPMGauge( real((PUMP(3)%Speed/PUMP(3)%Trans_Ratio),8) )
- SPM1 = MP1SPMGauge
- PUMP(3)%SoundSPM = INT(PUMP(3)%Speed/PUMP(3)%Trans_Ratio)
- Call SetSoundMP3( PUMP(3)%SoundSPM )
-
-
-
- IF (PUMP(3)%Flow_Rate>0.) Then
- Call OpenCementPump()
- Else
- Call CloseCementPump()
- End if
-
-
-
-
-
- end subroutine Pump3_OnMode_Solver
|