module PumpsMain use CPumpsVariables use CDrillingConsoleVariables use CDataDisplayConsoleVariables use CSimulationVariables use Pump_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 implicit none end subroutine Pump1_Init !!Extracted from pump1MainBody subroutine Pump1_Step use CWarningsVariables integer,dimension(8) :: MP_START_TIME, MP_END_TIME INTEGER :: MP_SolDuration if (PUMP(1)%PowerFailMalf==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() end if ! Pump1 Warning ----> Failure if (Pump1Failure==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() end if ! Pump3 Malfunction ----> Power Failure if (PUMP(3)%PowerFailMalf==1) then Call Pump3_OffMode_Solver !Call ClosePump3() end if ! Pump3 Warning ----> Failure if (Pump3Failure==1) then Call Pump3_OffMode_Solver !Call ClosePump3() end if !print*, 'MP1Throttle=', MP1Throttle 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. (MP1Throttle==0.) .and. (PUMP(1)%PowerFailMalf==0)) then !print*, 'pumps on' !print*, 'PUMP(1)%AssignmentSwitchh=' , PUMP(1)%AssignmentSwitchh PUMP(1)%SoundBlower = .true. Call SetSoundBlowerMP1(PUMP(1)%SoundBlower) MP1BLWR = 1 loop2: do Call DrillingConsole_ScrLEDs Call Pump_Total_Counts Call DATE_AND_TIME(values=MP_START_TIME) ! Pump1 Malfunction ----> Power Failure if (PUMP(1)%PowerFailMalf==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if ! Pump1 Warning ----> Failure if (Pump1Failure==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if 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 !print*, 'PUMP(1)%N_ref=' , PUMP(1)%N_ref , MP1Throttle 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 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)) !print*, 'MPtime=', MP_SolDuration if(MP_SolDuration > 0.0) then Call sleepqq(MP_SolDuration) end if if (IsPortable) then PUMP(1)%AssignmentSwitchh = 1 else PUMP(1)%AssignmentSwitchh = AssignmentSwitch end if if ((any(PUMP(1)%AssignmentSwitchh==(/5,6,7,8,11,12/))) .or. (MP1CPSwitch/=-1) .or. (IsStopped == .true.)) then PUMP(1)%SoundBlower = .false. Call SetSoundBlowerMP1(PUMP(1)%SoundBlower) MP1BLWR = 0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if end do loop2 else if( (MP1CPSwitch==1) .and. (MP1Throttle==0.) .and. (PUMP(3)%PowerFailMalf==0) ) then loop3: do Call DATE_AND_TIME(values=MP_START_TIME) !print*, 'PUMP(3) is on' ! Pump3 Malfunction ----> Power Failure if (PUMP(3)%PowerFailMalf==1) then Call Pump3_OffMode_Solver !Call ClosePump3() exit loop3 end if ! Pump3 Warning ----> Failure if (Pump3Failure==1) then !MP1BLWR=0 Call Pump3_OffMode_Solver !Call ClosePump3() !????????????? exit loop3 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(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)) !print*, 'MPtime=', MP_SolDuration if(MP_SolDuration > 0.0) then Call sleepqq(MP_SolDuration) end if if ((MP1CPSwitch/=1) .or. (IsStopped == .true.)) then Call Pump3_OffMode_Solver Call CloseCementPump() exit loop3 end if end do loop3 else !print*, 'pumps off' if (IsPortable) then PUMP(1)%AssignmentSwitchh = 1 !print*, 'PUMP(1)%AssignmentSwitchh2=' , PUMP(1)%AssignmentSwitchh else PUMP(1)%AssignmentSwitchh = AssignmentSwitch !print*, 'PUMP(1)%AssignmentSwitchh22=' , PUMP(1)%AssignmentSwitchh , AssignmentSwitch end if if ((any(PUMP(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (MP1CPSwitch==-1)) 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() !print*, 'PUMP(1)%off=', PUMP(1)%dt , PUMP(1)%ia , PUMP(1)%w , PUMP(1)%n , PUMP(1)%x end if end subroutine Pump1_Step subroutine Pump1_Output implicit none end subroutine Pump1_Output subroutine Pump1MainBody use ifport use ifmt use CWarningsVariables !use equipments_PowerLimit implicit none integer,dimension(8) :: MP_START_TIME, MP_END_TIME INTEGER :: MP_SolDuration Call Pump_StartUp loop1 : do Call sleepqq(10) Call DrillingConsole_ScrLEDs !Call Pump_Total_Counts ! Pump1 Malfunction ----> Power Failure if (PUMP(1)%PowerFailMalf==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() end if ! Pump1 Warning ----> Failure if (Pump1Failure==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() end if ! Pump3 Malfunction ----> Power Failure if (PUMP(3)%PowerFailMalf==1) then Call Pump3_OffMode_Solver !Call ClosePump3() end if ! Pump3 Warning ----> Failure if (Pump3Failure==1) then Call Pump3_OffMode_Solver !Call ClosePump3() end if !print*, 'MP1Throttle=', MP1Throttle 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. (MP1Throttle==0.) .and. (PUMP(1)%PowerFailMalf==0)) then !print*, 'pumps on' !print*, 'PUMP(1)%AssignmentSwitchh=' , PUMP(1)%AssignmentSwitchh PUMP(1)%SoundBlower = .true. Call SetSoundBlowerMP1(PUMP(1)%SoundBlower) MP1BLWR = 1 loop2: do Call DrillingConsole_ScrLEDs Call Pump_Total_Counts Call DATE_AND_TIME(values=MP_START_TIME) ! Pump1 Malfunction ----> Power Failure if (PUMP(1)%PowerFailMalf==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if ! Pump1 Warning ----> Failure if (Pump1Failure==1) then !MP1BLWR=0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if 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 !print*, 'PUMP(1)%N_ref=' , PUMP(1)%N_ref , MP1Throttle 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 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)) !print*, 'MPtime=', MP_SolDuration if(MP_SolDuration > 0.0) then Call sleepqq(MP_SolDuration) end if if (IsPortable) then PUMP(1)%AssignmentSwitchh = 1 else PUMP(1)%AssignmentSwitchh = AssignmentSwitch end if if ((any(PUMP(1)%AssignmentSwitchh==(/5,6,7,8,11,12/))) .or. (MP1CPSwitch/=-1) .or. (IsStopped == .true.)) then PUMP(1)%SoundBlower = .false. Call SetSoundBlowerMP1(PUMP(1)%SoundBlower) MP1BLWR = 0 Call Pump1_OffMode_Solver(1) Call ClosePump1() exit loop2 end if end do loop2 else if( (MP1CPSwitch==1) .and. (MP1Throttle==0.) .and. (PUMP(3)%PowerFailMalf==0) ) then loop3: do Call DATE_AND_TIME(values=MP_START_TIME) !print*, 'PUMP(3) is on' ! Pump3 Malfunction ----> Power Failure if (PUMP(3)%PowerFailMalf==1) then Call Pump3_OffMode_Solver !Call ClosePump3() exit loop3 end if ! Pump3 Warning ----> Failure if (Pump3Failure==1) then !MP1BLWR=0 Call Pump3_OffMode_Solver !Call ClosePump3() !????????????? exit loop3 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(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)) !print*, 'MPtime=', MP_SolDuration if(MP_SolDuration > 0.0) then Call sleepqq(MP_SolDuration) end if if ((MP1CPSwitch/=1) .or. (IsStopped == .true.)) then Call Pump3_OffMode_Solver Call CloseCementPump() exit loop3 end if end do loop3 else !print*, 'pumps off' if (IsPortable) then PUMP(1)%AssignmentSwitchh = 1 !print*, 'PUMP(1)%AssignmentSwitchh2=' , PUMP(1)%AssignmentSwitchh else PUMP(1)%AssignmentSwitchh = AssignmentSwitch !print*, 'PUMP(1)%AssignmentSwitchh22=' , PUMP(1)%AssignmentSwitchh , AssignmentSwitch end if if ((any(PUMP(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (MP1CPSwitch==-1)) 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() !print*, 'PUMP(1)%off=', PUMP(1)%dt , PUMP(1)%ia , PUMP(1)%w , PUMP(1)%n , PUMP(1)%x end if if (IsStopped == .true.) then exit loop1 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 implicit none 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 sleepqq(10) ! Pump2 Malfunction ----> Power Failure if (PUMP(2)%PowerFailMalf==1) then Call ClosePump2() !MP2BLWR=0 Call Pump2_OffMode_Solver(2) end if ! Pump2 Warning ----> Failure if (Pump2Failure==1) then !MP1BLWR=0 Call Pump2_OffMode_Solver(2) Call ClosePump2() end if if (IsPortable) then PUMP(2)%AssignmentSwitchh = 1 else PUMP(2)%AssignmentSwitchh = AssignmentSwitch end if if((any(PUMP(2)%AssignmentSwitchh==(/1,2,3,4,5,7,8,11/))) .and. (MP2Switch==1) .and. (MP2Throttle==0.).and. (PUMP(2)%PowerFailMalf==0)) then PUMP(2)%SoundBlower = .true. Call SetSoundBlowerMP2(PUMP(2)%SoundBlower) MP2BLWR = 1 loop2: do CALL DATE_AND_TIME(values=MP_START_TIME) ! Pump2 Malfunction ----> Power Failure if (PUMP(2)%PowerFailMalf==1) then Call ClosePump2() !MP2BLWR=0 Call Pump2_OffMode_Solver(2) exit loop2 end if ! Pump2 Warning ----> Failure if (Pump2Failure==1) then Call ClosePump2() !MP2BLWR=0 Call Pump2_OffMode_Solver(2) exit loop2 end if PUMP(2)%N_new = MP2Throttle if (((PUMP(2)%N_new-PUMP(2)%N_old)/PUMP(2)%time_step)>193.) then PUMP(2)%N_ref = (193.*PUMP(2)%time_step)+PUMP(2)%N_old else if (((PUMP(2)%N_old-PUMP(2)%N_new)/PUMP(2)%time_step)>193.) then PUMP(2)%N_ref = (-193.*PUMP(2)%time_step)+PUMP(2)%N_old else PUMP(2)%N_ref = PUMP(2)%N_new end if Call Pump2_OnMode_Solver(2) !IF (PUMP(2)%Flow_Rate>0.) Then ! Call OpenPump2() !Else ! Call ClosePump2() !End if PUMP(2)%N_old=PUMP(2)%N_ref 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)) !print*, 'MPtime=', MP_SolDuration if(MP_SolDuration > 0.0d0) then CALL sleepqq(MP_SolDuration) end if if (IsPortable) then PUMP(2)%AssignmentSwitchh = 1 else PUMP(2)%AssignmentSwitchh = AssignmentSwitch end if if ((any(PUMP(2)%AssignmentSwitchh==(/6,9,10,12/))) .or. (MP2Switch==0) .or. (IsStopped == .true.)) then Call ClosePump2() PUMP(2)%SoundBlower = .false. Call SetSoundBlowerMP2(PUMP(2)%SoundBlower) MP2BLWR = 0 Call Pump2_OffMode_Solver(2) exit loop2 end if end do loop2 else if (IsPortable) then PUMP(2)%AssignmentSwitchh = 1 else PUMP(2)%AssignmentSwitchh = AssignmentSwitch end if if((any(PUMP(2)%AssignmentSwitchh==(/1,2,3,4,5,7,8,11/))) .and. (MP2Switch==1)) then PUMP(2)%SoundBlower = .true. Call SetSoundBlowerMP2(PUMP(2)%SoundBlower) MP2BLWR = 1 else PUMP(2)%SoundBlower = .false. Call SetSoundBlowerMP2(PUMP(2)%SoundBlower) MP2BLWR = 0 end if PUMP(2)%N_ref = MP2Throttle Call ClosePump2() Call Pump2_OffMode_Solver(2) 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