|
- module PumpsMain
-
- use CPumpsVariables
- use CDrillingConsoleVariables
- use CDataDisplayConsoleVariables
- use CSimulationVariables
- use Pumps_VARIABLES
- use CSounds
-
- implicit none
- public
-
- contains
-
-
-
- ! ****************************************
- ! ***** subroutine Pump1MainBody *****
- ! ****************************
-
- subroutine Pump1_Setup()
- use CSimulationVariables
- implicit none
- call OnSimulationInitialization%Add(Pump1_Init)
- call OnSimulationStop%Add(Pump1_Init)
- call OnPump1Step%Add(Pump1_Step)
- call OnPump1Output%Add(Pump1_Output)
- call OnPump1Main%Add(Pump1MainBody)
- end subroutine
-
- subroutine Pump1_Init
- Call Pumps_StartUp
- end subroutine Pump1_Init
-
- subroutine Pump1_Step
- Call Pump1_MainSolver
- end subroutine Pump1_Step
-
- subroutine Pump1_Output
- implicit none
- end subroutine Pump1_Output
-
- subroutine Pump1MainBody
- use ifport
- use ifmt
- !use Pump1_MainSolver
- use CWarningsVariables
- !use equipments_PowerLimit
- implicit none
-
- integer,dimension(8) :: MP_START_TIME, MP_END_TIME
- INTEGER :: MP_SolDuration
-
-
- Call Pumps_StartUp
- loop1 : do
- !!Call sleepqq(10)
- !!Call DATE_AND_TIME(values=MP_START_TIME)
-
- Call Pump1_MainSolver
-
- if (Pumps_IsStopped == .true.) then
- exit loop1
- end if
-
- !!Call DATE_AND_TIME(values=MP_END_TIME)
- !!MP_SolDuration = 100-(MP_END_TIME(5)*3600000+MP_END_TIME(6)*60000+MP_END_TIME(7)*1000+MP_END_TIME(8)-MP_START_TIME(5)*3600000-MP_START_TIME(6)*60000-MP_START_TIME(7)*1000-MP_START_TIME(8))
- !!if(MP_SolDuration > 0.0) then
- !! Call sleepqq(MP_SolDuration)
- !!end if
- end do loop1
-
- end subroutine Pump1MainBody
-
-
-
-
-
- ! ****************************************
- ! ***** subroutine Pump2MainBody *****
- ! ****************************
- ! subroutine Pump2_Setup()
- ! use CSimulationVariables
- ! implicit none
- ! call OnSimulationInitialization%Add(Pump2_Init)
- ! call OnSimulationStop%Add(Pump2_Init)
- ! call OnPump2Step%Add(Pump2_Step)
- ! call OnPump2Output%Add(Pump2_Output)
- ! call OnPump2Main%Add(Pump2MainBody)
- ! end subroutine
- !
- ! subroutine Pump2_Init
- ! implicit none
- ! end subroutine Pump2_Init
- !
- ! subroutine Pump2_Step
- ! call Pump2_MainSolver
- ! end subroutine Pump2_Step
- !
- ! subroutine Pump2_Output
- ! implicit none
- ! end subroutine Pump2_Output
- !
- ! subroutine Pump2MainBody
- ! use ifport
- ! use ifmt
- ! use CWarningsVariables
- ! implicit none
- !
- ! integer,dimension(8) :: MP_START_TIME, MP_END_TIME
- ! INTEGER :: MP_SolDuration
- !
- ! Call Pump_StartUp
- !
- ! loop1 : do
- !
- ! Call DATE_AND_TIME(values=MP_START_TIME)
- !
- ! Call Pump2_MainSolver
- !
- ! Call DATE_AND_TIME(values=MP_END_TIME)
- ! MP_SolDuration = 100-(MP_END_TIME(5)*3600000+MP_END_TIME(6)*60000+MP_END_TIME(7)*1000+MP_END_TIME(8)-MP_START_TIME(5)*3600000-MP_START_TIME(6)*60000-MP_START_TIME(7)*1000-MP_START_TIME(8))
- ! if(MP_SolDuration > 0.0) then
- ! Call sleepqq(MP_SolDuration)
- ! end if
- !
- ! if (IsStopped == .true.) then
- ! exit loop1
- ! end if
- !
- ! end do loop1
- !
- !
- ! end subroutine Pump2MainBody
- !
- !
- !
- !
- !! ****************************************
- !! ***** subroutine Pump3MainBody *****
- !! ****************************
- ! subroutine Pump3_Setup()
- ! use CSimulationVariables
- ! implicit none
- ! call OnSimulationInitialization%Add(Pump3_Init)
- ! call OnSimulationStop%Add(Pump3_Init)
- ! call OnPump3Step%Add(Pump3_Step)
- ! call OnPump3Output%Add(Pump3_Output)
- ! call OnPump3Main%Add(Pump3MainBody)
- ! end subroutine
- !
- ! subroutine Pump3_Init
- ! implicit none
- ! end subroutine Pump3_Init
- !
- ! subroutine Pump3_Step
- ! implicit none
- ! end subroutine Pump3_Step
- !
- ! subroutine Pump3_Output
- ! implicit none
- ! end subroutine Pump3_Output
- !
- ! subroutine Pump3MainBody
- ! use ifport
- ! use ifmt
- ! implicit none
- !
- !
- ! integer,dimension(8) :: MP_START_TIME, MP_END_TIME
- ! INTEGER :: MP_SolDuration
- !
- ! !Call Pump_StartUp
- ! !loop1 : do
- ! !
- ! ! Call sleepqq(10)
- ! !
- ! ! !!! Pump3 Malfunction ----> Power Failure
- ! ! !!if (PUMP(1)%PowerFailMalf==1) then
- ! ! !! !MP1BLWR=0
- ! ! !! Call Pump3_OffMode_Solver
- ! ! !! Call ClosePump1()
- ! ! !!end if
- ! !
- ! ! !if( (MP1CPSwitch==1) .and. (MP1Throttle==0.) .and. (PUMP(3)%PowerFailMalf==0) ) then
- ! !!
- ! !! loop2: do
- ! !!
- ! !! Call DATE_AND_TIME(values=MP_START_TIME)
- ! !!
- ! !!!! ! Pump3 Malfunction ----> Power Failure
- ! !!!! if (PUMP(1)%PowerFailMalf==1) then
- ! !!!! !MP1BLWR=0
- ! !!!! Pump3_OffMode_Solver
- ! !!!! Call ClosePump1()
- ! !!!! exit loop2
- ! !!!! end if
- ! !!
- ! !! 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
- ! !!
- ! !! Call DATE_AND_TIME(values=MP_END_TIME)
- ! !! MP_SolDuration = 100-(MP_END_TIME(6)*60000+MP_END_TIME(7)*1000+MP_END_TIME(8)-MP_START_TIME(6)*60000-MP_START_TIME(7)*1000-MP_START_TIME(8))
- ! !! !print*, 'MPtime=', MP_SolDuration
- ! !! if(MP_SolDuration > 0.0) then
- ! !! Call sleepqq(MP_SolDuration)
- ! !! end if
- ! !!
- ! !! if ((MP1CPSwitch==0) .or. (IsStopped == .true.)) then
- ! !! Call Pump3_OffMode_Solver
- ! !! Call CloseCementPump()
- ! !! exit loop2
- ! !! end if
- ! !! end do loop2
- ! !
- ! ! else
- ! !
- ! ! !Call Pump3_OffMode_Solver
- ! ! !Call CloseCementPump()
- ! !
- ! ! end if
- ! !
- ! ! if (IsStopped == .true.) then
- ! ! exit loop1
- ! ! end if
- ! !
- ! !end do loop1
- !
- !
- ! end subroutine Pump3MainBody
-
- end module PumpsMain
|