|
- subroutine Pump1_MainSolver
-
- use Pump_VARIABLES
- use CPumpsVariables
- use CDrillingConsoleVariables
- use CDataDisplayConsoleVariables
- use CSimulationVariables
- use CDrillWatchVariables
- use equipments_PowerLimit
- use CSounds
- use CWarningsVariables
-
-
- IMPLICIT NONE
-
-
- Call DrillingConsole_ScrLEDs
- Call Pump_Total_Counts
-
- if (MP1Throttle<=0.e0) then
- PUMP(1)%K_throttle = 1
- end if
-
- if (IsPortable) then
- PUMP(1)%AssignmentSwitchh = 1
- else
- PUMP(1)%AssignmentSwitchh = AssignmentSwitch
- end if
-
- if((any(PUMP(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (MP1CPSwitch==-1) .and. (PUMP(1)%K_throttle==1) .and. (PUMP(1)%PowerFailMalf==0) .and. (Pump1Failure==0) .and. (IsStopped == .false.)) then
-
- PUMP(1)%SoundBlower = .true.
- Call SetSoundBlowerMP1(PUMP(1)%SoundBlower)
- MP1BLWR = 1
-
- !Call DrillingConsole_ScrLEDs
- !Call Pump_Total_Counts
-
-
- PUMP(1)%N_new = MP1Throttle
- if (((PUMP(1)%N_new-PUMP(1)%N_old)/PUMP(1)%time_step)>193.) then
- PUMP(1)%N_ref =(193.*PUMP(1)%time_step)+PUMP(1)%N_old
- else if (((PUMP(1)%N_old-PUMP(1)%N_new)/PUMP(1)%time_step)>193.) then
- PUMP(1)%N_ref = (-193.*PUMP(1)%time_step)+PUMP(1)%N_old
- else
- PUMP(1)%N_ref = PUMP(1)%N_new
- end if
-
- Call Pump1_OnMode_Solver(1)
-
- !IF (PUMP(1)%Flow_Rate>0.) Then
- ! Call OpenPump1()
- !Else
- ! Call ClosePump1()
- !End if
-
- PUMP(1)%N_old = PUMP(1)%N_ref
-
-
-
- else if( (MP1CPSwitch==1) .and. (PUMP(1)%K_throttle==1) .and. (PUMP(3)%PowerFailMalf==0) .and. (Pump3Failure==0) .and. (IsStopped == .false.)) then
-
-
- PUMP(3)%N_new = MP1Throttle
- if (((PUMP(3)%N_new-PUMP(3)%N_old)/PUMP(3)%time_step)>193.) then
- PUMP(3)%N_ref =(193.*PUMP(3)%time_step)+PUMP(3)%N_old
- else if (((PUMP(3)%N_old-PUMP(3)%N_new)/PUMP(3)%time_step)>193.) then
- PUMP(3)%N_ref = (-193.*PUMP(3)%time_step)+PUMP(3)%N_old
- else
- PUMP(3)%N_ref = PUMP(3)%N_new
- end if
-
- Call Pump3_OnMode_Solver
-
- IF (PUMP(3)%Flow_Rate>0.) Then
- Call OpenCementPump()
- Else
- Call CloseCementPump()
- End if
-
- PUMP(3)%N_old = PUMP(3)%N_ref
-
-
-
- else
-
- if ((any(PUMP(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (MP1CPSwitch==-1) .and. (IsStopped == .false.)) then
- PUMP(1)%SoundBlower = .true.
- Call SetSoundBlowerMP1(PUMP(1)%SoundBlower)
- MP1BLWR = 1
- else
- PUMP(1)%SoundBlower = .false.
- Call SetSoundBlowerMP1(PUMP(1)%SoundBlower)
- MP1BLWR = 0
- end if
-
-
- Call Pump1_OffMode_Solver(1)
- Call ClosePump1()
- Call Pump3_OffMode_Solver
- Call CloseCementPump()
-
- PUMP(1)%K_throttle = 0
-
-
- end if
-
-
- end subroutine Pump1_MainSolver
|