|
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667 |
- subroutine Pump2_OffMode_Solver(Pump_No)
-
- use Pump_VARIABLES
- use CPumpsVariables
- use CDrillingConsoleVariables
- use CDataDisplayConsoleVariables
- use CSimulationVariables
- use CDrillWatchVariables
- use CSounds
-
-
- IMPLICIT NONE
- INTEGER :: Pump_No
-
-
-
- CALL Pump_INPUTS
-
-
-
- !==================================================================
- ! Rate limit for off Mode
-
- if (((PUMP(Pump_No)%N_old-0.0d0)/PUMP(Pump_No)%time_step)>386.) then
- PUMP(Pump_No)%N_ref = (-386.*PUMP(Pump_No)%time_step)+PUMP(Pump_No)%N_old
- !else
- ! PUMP(1)%N_ref=0.0d0
- !end if
-
- Call Pump2_OnMode_Solver(Pump_No)
-
- PUMP(Pump_No)%N_old = PUMP(Pump_No)%N_ref
-
- !==================================================================
- else
-
-
- PUMP(Pump_No)%Speed = 0.0d0
- PUMP(Pump_No)%w = 0.0d0
- PUMP(Pump_No)%w_old = 0.0d0
- PUMP(Pump_No)%w_new = 0.0d0
- PUMP(Pump_No)%ia = 0.0d0
- PUMP(Pump_No)%ia_old = 0.0d0
- PUMP(Pump_No)%ia_new = 0.0d0
- PUMP(Pump_No)%x = 0.0d0
- PUMP(Pump_No)%x_old = 0.0d0
- PUMP(Pump_No)%x_new = 0.0d0
-
-
-
- Call Pump_Solver(Pump_No)
-
- Call Pump_Total_Counts
-
-
-
- !Call Set_MP1SPMGauge( real((PUMP(1)%Speed/PUMP(1)%Trans_Ratio),8) )
- !SPM1 = MP1SPMGauge
- Call Set_MP2SPMGauge( sngl(1-PUMP(2)%SPMGaugeMalf)*real((PUMP(2)%Speed/PUMP(2)%Trans_Ratio),8) )
- SPM2 = MP2SPMGauge
- PUMP(2)%SoundSPM = INT(PUMP(2)%Speed/PUMP(2)%Trans_Ratio)
- Call SetSoundMP2( PUMP(2)%SoundSPM )
-
-
- end if
-
- end subroutine Pump2_OffMode_Solver
|