module PumpsMain use SimulationVariables 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 Pumps_MainSolver use SimulationVariables Implicit none Call DrillingConsole_ScrLEDs !koja bezaramesh????? Call Pumps_Inputs Call Pump1_MainSolver Call Pump2_MainSolver Call Pump3_MainSolver Call Pumps_TotalSolver Call Pumps_Outputs end subroutine Pumps_MainSolver subroutine Pumps_Inputs use CDrillingConsoleVariables use SimulationVariables Use MudSystemModule IMPLICIT NONE !>>>>>>>>>>>>>>>>>>>>>>> PUMP 1 <<<<<<<<<<<<<<<<<<<<<<<<<<< !data%State%Pump(1)%BlowPopOffMalf = 0 !??????? motaghayere voroudi if ( data%State%Pump(1)%BlowPopOffMalf==1 ) then ! Pump1 Malfunction ----> Blow Pop-offs (Relief Valves) data%State%Pump(1)%StandPipe_Pressure = 0.d0 else data%State%Pump(1)%StandPipe_Pressure = PumpPressure1 ![psi] if ( data%State%Pump(1)%StandPipe_Pressure<=14.d0 ) then data%State%Pump(1)%StandPipe_Pressure = 14.d0 end if end if data%State%Pump(1)%AssignmentSwitchh = data%Equipments%DrillingConsole%AssignmentSwitch data%State%Pump(1)%Switch = data%Equipments%DrillingConsole%MP1CPSwitch data%State%Pump(1)%Throttle = data%Equipments%DrillingConsole%MP1Throttle ![SPM] 0 Power Failure) !dar CPumpProblemsVariables meghdardehi mishavad data%State%Pump(1)%Failure = data%Warnings%Pump1Failure !(Pump1 Warning ----> Failure) data%State%Pump(1)%N_new = data%State%Pump(1)%Throttle !>>>>>>>>>>>>>>>>>>>>>>> PUMP 2 <<<<<<<<<<<<<<<<<<<<<<<<<<< !data%State%Pump(2)%BlowPopOffMalf = 0 !??????? motaghayere voroudi if ( data%State%Pump(2)%BlowPopOffMalf==1 ) then ! Pump2 Malfunction ----> Blow Pop-offs (Relief Valves) data%State%Pump(2)%StandPipe_Pressure = 0.d0 else data%State%Pump(2)%StandPipe_Pressure = PumpPressure2 ![psi] if ( data%State%Pump(2)%StandPipe_Pressure<=14.d0 ) then data%State%Pump(2)%StandPipe_Pressure = 14.d0 end if end if data%State%Pump(2)%AssignmentSwitchh = data%Equipments%DrillingConsole%AssignmentSwitch data%State%Pump(2)%Switch = data%Equipments%DrillingConsole%MP2Switch data%State%Pump(2)%Throttle = data%Equipments%DrillingConsole%MP2Throttle ![SPM] 0 Power Failure) !dar CPumpProblemsVariables meghdardehi mishavad data%State%Pump(2)%Failure = data%Warnings%Pump2Failure !(Pump2 Warning ----> Failure) data%State%Pump(2)%N_new = data%State%Pump(2)%Throttle !!>>>>>>>>>>>>>>>>>>>>>>> PUMP 3 <<<<<<<<<<<<<<<<<<<<<<<<<<< !data%State%Pump(3)%BlowPopOffMalf = 0 !??????? motaghayere voroudi if ( data%State%Pump(3)%BlowPopOffMalf==1 ) then ! Pump3 Malfunction ----> Blow Pop-offs (Relief Valves) data%State%Pump(3)%StandPipe_Pressure = 0.d0 else data%State%Pump(3)%StandPipe_Pressure = PumpPressure3 ![psi] if ( data%State%Pump(3)%StandPipe_Pressure<=14.d0 ) then data%State%Pump(3)%StandPipe_Pressure = 14.d0 end if end if data%State%Pump(3)%Switch = data%Equipments%DrillingConsole%MP1CPSwitch data%State%Pump(3)%Throttle = data%Equipments%DrillingConsole%MP1Throttle ![SPM] 0 Power Failure) !dar CPumpProblemsVariables meghdardehi mishavad data%State%Pump(3)%Failure = data%Warnings%Pump3Failure !(Pump1 Warning ----> Failure) data%State%Pump(3)%N_new = data%State%Pump(3)%Throttle !>>>>>>>>>>>>>>>>>>>>>>> Total Pumps <<<<<<<<<<<<<<<<<<<<<<<<<<< end subroutine Pumps_Inputs subroutine DrillingConsole_ScrLEDs use CDrillingConsoleVariables use SimulationVariables use SimulationVariables use SimulationVariables !@ IMPLICIT NONE !===> Torque Limit data%Equipments%DrillingConsole%RTTorqueLimitGauge = sngl(1-data%State%RTable%TorqueLimitGaugeMalf)*(data%Equipments%DrillingConsole%RTTorqueLimitKnob/10.d0)*7000.d0 !tabdile bazeye 0-10 be 0-7000 taghribi anjam shode, baadan eslah shavad ?????? if((any(data%Equipments%DrillingConsole%AssignmentSwitch==(/1,2,3,4,8,9,10,11/)))) then data%Equipments%DrillingConsole%SCR1LED=1 data%Equipments%DrillingConsole%SCR2LED=1 data%Equipments%DrillingConsole%SCR3LED=1 data%Equipments%DrillingConsole%SCR4LED=1 else if (data%Equipments%DrillingConsole%AssignmentSwitch == 5) then data%Equipments%DrillingConsole%SCR1LED=1 data%Equipments%DrillingConsole%SCR2LED=1 data%Equipments%DrillingConsole%SCR3LED=0 data%Equipments%DrillingConsole%SCR4LED=1 else if (data%Equipments%DrillingConsole%AssignmentSwitch == 7) then data%Equipments%DrillingConsole%SCR1LED=1 data%Equipments%DrillingConsole%SCR2LED=1 data%Equipments%DrillingConsole%SCR3LED=1 data%Equipments%DrillingConsole%SCR4LED=0 else data%Equipments%DrillingConsole%SCR1LED=0 data%Equipments%DrillingConsole%SCR2LED=0 data%Equipments%DrillingConsole%SCR3LED=0 data%Equipments%DrillingConsole%SCR4LED=0 end if end subroutine DrillingConsole_ScrLEDs subroutine Pump1_MainSolver use SimulationVariables Implicit none if (data%State%Pump(1)%Throttle<=0.d0) then data%State%Pump(1)%K_throttle = 1 end if if((any(data%State%Pump(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (data%State%Pump(1)%Switch==-1) .and. (data%State%Pump(1)%K_throttle==1) .and. (data%State%Pump(1)%PowerFailMalf==0) .and. (data%State%Pump(1)%Failure==0)) then data%State%Pump(1)%SoundBlower = .true. data%State%Pump(1)%BLWR = 1 !========================== Pump 1 Rate limit ========================== if (((data%State%Pump(1)%N_new-data%State%Pump(1)%N_old)/data%State%Pump(1)%time_step)>data%State%Pump(1)%RateChange) then data%State%Pump(1)%Speed =(data%State%Pump(1)%RateChange*data%State%Pump(1)%time_step)+data%State%Pump(1)%N_old ![RPM] else if (((data%State%Pump(1)%N_old-data%State%Pump(1)%N_new)/data%State%Pump(1)%time_step)>data%State%Pump(1)%RateChange) then data%State%Pump(1)%Speed = (-data%State%Pump(1)%RateChange*data%State%Pump(1)%time_step)+data%State%Pump(1)%N_old else data%State%Pump(1)%Speed = data%State%Pump(1)%N_new end if !======================================================================= Call Pump_OnMode_Solver(1) else if ((any(data%State%Pump(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (data%State%Pump(1)%Switch==-1)) then data%State%Pump(1)%SoundBlower = .true. else data%State%Pump(1)%SoundBlower = .false. end if if ((any(data%State%Pump(1)%AssignmentSwitchh==(/1,2,3,4,9,10/))) .and. (data%State%Pump(1)%Switch==-1) .and. (data%State%Pump(1)%PowerFailMalf==0) .and. (data%State%Pump(1)%Failure==0)) then data%State%Pump(1)%BLWR = 1 else data%State%Pump(1)%BLWR = 0 end if Call Pump_OffMode_Solver(1) data%State%Pump(1)%K_throttle = 0 end if data%State%Pump(1)%N_old = data%State%Pump(1)%Speed end subroutine Pump1_MainSolver subroutine Pump2_MainSolver use SimulationVariables Implicit none if (data%State%Pump(2)%Throttle<=0.d0) then data%State%Pump(2)%K_throttle = 1 end if if((any(data%State%Pump(2)%AssignmentSwitchh==(/1,2,3,4,5,7,8,11/))) .and. (data%State%Pump(2)%Switch==-1) .and. (data%State%Pump(2)%K_throttle==1) .and. (data%State%Pump(2)%PowerFailMalf==0) .and. (data%State%Pump(2)%Failure==0)) then data%State%Pump(2)%SoundBlower = .true. data%State%Pump(2)%BLWR = 1 !========================== Pump 2 Rate limit ========================== if (((data%State%Pump(2)%N_new-data%State%Pump(2)%N_old)/data%State%Pump(2)%time_step)>data%State%Pump(2)%RateChange) then data%State%Pump(2)%Speed =(data%State%Pump(2)%RateChange*data%State%Pump(2)%time_step)+data%State%Pump(2)%N_old ![RPM] else if (((data%State%Pump(2)%N_old-data%State%Pump(2)%N_new)/data%State%Pump(2)%time_step)>data%State%Pump(2)%RateChange) then data%State%Pump(2)%Speed = (-data%State%Pump(2)%RateChange*data%State%Pump(2)%time_step)+data%State%Pump(2)%N_old else data%State%Pump(2)%Speed = data%State%Pump(2)%N_new end if !======================================================================= Call Pump_OnMode_Solver(2) else if ((any(data%State%Pump(2)%AssignmentSwitchh==(/1,2,3,4,5,7,8,11/))) .and. (data%State%Pump(2)%Switch==-1)) then data%State%Pump(2)%SoundBlower = .true. else data%State%Pump(2)%SoundBlower = .false. end if if ((any(data%State%Pump(2)%AssignmentSwitchh==(/1,2,3,4,5,7,8,11/))) .and. (data%State%Pump(2)%Switch==-1) .and. (data%State%Pump(2)%PowerFailMalf==0) .and. (data%State%Pump(2)%Failure==0)) then data%State%Pump(2)%BLWR = 1 else data%State%Pump(2)%BLWR = 0 end if Call Pump_OffMode_Solver(2) data%State%Pump(2)%K_throttle = 0 end if data%State%Pump(2)%N_old = data%State%Pump(2)%Speed end subroutine Pump2_MainSolver subroutine Pump3_MainSolver use SimulationVariables Implicit none if (data%State%Pump(3)%Throttle<=0.d0) then data%State%Pump(3)%K_throttle = 1 end if if((data%State%Pump(3)%Switch==1) .and. (data%State%Pump(3)%K_throttle==1) .and. (data%State%Pump(3)%PowerFailMalf==0) .and. (data%State%Pump(3)%Failure==0)) then !========================== Pump 3 Rate limit ========================== if (((data%State%Pump(3)%N_new-data%State%Pump(3)%N_old)/data%State%Pump(3)%time_step)>data%State%Pump(3)%RateChange) then data%State%Pump(3)%Speed =(data%State%Pump(3)%RateChange*data%State%Pump(3)%time_step)+data%State%Pump(3)%N_old ![RPM] else if (((data%State%Pump(3)%N_old-data%State%Pump(3)%N_new)/data%State%Pump(3)%time_step)>data%State%Pump(3)%RateChange) then data%State%Pump(3)%Speed = (-data%State%Pump(3)%RateChange*data%State%Pump(3)%time_step)+data%State%Pump(3)%N_old else data%State%Pump(3)%Speed = data%State%Pump(3)%N_new end if !======================================================================= Call Pump_OnMode_Solver(3) else Call Pump_OffMode_Solver(3) data%State%Pump(3)%K_throttle = 0 end if data%State%Pump(3)%N_old = data%State%Pump(3)%Speed end subroutine Pump3_MainSolver subroutine Pumps_TotalSolver use SimulationVariables Implicit none data%Equipments%MPumps%Total_Pump_Gpm = data%State%Pump(1)%Flow_Rate+data%State%Pump(2)%Flow_Rate+data%State%Pump(3)%Flow_Rate ![gpm] data%Equipments%MPumps%Total_Pump_SPM = (data%State%Pump(1)%Speed/data%State%Pump(1)%Trans_Ratio)+(data%State%Pump(2)%Speed/data%State%Pump(2)%Trans_Ratio)+(data%State%Pump(3)%Speed/data%State%Pump(3)%Trans_Ratio) ![stk/min] end subroutine Pumps_TotalSolver subroutine Pumps_Outputs use CDataDisplayConsole use SimulationVariables Use MudSystemModule Use CSounds IMPLICIT NONE !>>>>>>>>>>>>>>>>>>>>>>> PUMP 1 <<<<<<<<<<<<<<<<<<<<<<<<<<< If (data%State%Pump(1)%Open_Close==1) then Call OpenPump1() Else if (data%State%Pump(1)%Open_Close==0) then Call ClosePump1() End if data%Equipments%DrillingConsole%MP1BLWR = data%State%Pump(1)%BLWR Call SetSoundBlowerMP1( data%State%Pump(1)%SoundBlower ) !.true. or .false. Call SetSoundMP1( data%State%Pump(1)%SoundSPM ) ![SPM] , integer if ((data%State%Pump(1)%Switch==-1) .or. (data%State%Pump(1)%Switch==0)) then Call Set_MP1SPMGauge( sngl(1-data%State%Pump(1)%SPMGaugeMalf)*real((data%State%Pump(1)%Speed/data%State%Pump(1)%Trans_Ratio),8) ) ![spm] , real data%Equipments%DrillingWatch%SPM1 = data%Equipments%DataDisplayConsole%MP1SPMGauge end if !data%State%Pump(1)%Flow_Rate !to other modules , [gpm] !>>>>>>>>>>>>>>>>>>>>>>> PUMP 2 <<<<<<<<<<<<<<<<<<<<<<<<<<< If (data%State%Pump(2)%Open_Close==1) then Call OpenPump2() Else if (data%State%Pump(2)%Open_Close==0) then Call ClosePump2() End if data%Equipments%DrillingConsole%MP2BLWR = data%State%Pump(2)%BLWR Call SetSoundBlowerMP2( data%State%Pump(2)%SoundBlower ) Call SetSoundMP2( data%State%Pump(2)%SoundSPM ) ![SPM] Call Set_MP2SPMGauge( sngl(1-data%State%Pump(2)%SPMGaugeMalf)*real((data%State%Pump(2)%Speed/data%State%Pump(2)%Trans_Ratio),8) ) ![SPM] data%Equipments%DrillingWatch%SPM2 = data%Equipments%DataDisplayConsole%MP2SPMGauge !data%State%Pump(2)%Flow_Rate !to other modules !!>>>>>>>>>>>>>>>>>>>>>>> PUMP 3 <<<<<<<<<<<<<<<<<<<<<<<<<<< If (data%State%Pump(3)%Open_Close==1) then Call OpenCementPump() Else if (data%State%Pump(3)%Open_Close==0) then Call CloseCementPump() End if Call SetSoundMP3( data%State%Pump(3)%SoundSPM ) if (data%State%Pump(3)%Switch==1) then Call Set_MP1SPMGauge( real((data%State%Pump(3)%Speed/data%State%Pump(3)%Trans_Ratio),8) ) ![SPM] SPMGaugeMalf Malf nadarad???? data%Equipments%DrillingWatch%SPM1 = data%Equipments%DataDisplayConsole%MP1SPMGauge end if !data%State%Pump(3)%Flow_Rate !to other modules !>>>>>>>>>>>>>>>>>>>>>>> Total Pumps <<<<<<<<<<<<<<<<<<<<<<<<<<< !data%Equipments%MPumps%Total_Pump_Gpm = 100.d0 !??????????? !data%Equipments%MPumps%Total_Pump_SPM = 1000.d0 !????????????? !SCR1LED=1 !SCR2LED=1 !SCR3LED=1 !SCR4LED=1 end subroutine Pumps_Outputs subroutine Pumps_StartUp use CPumpsVariables use CPumps use SimulationVariables IMPLICIT NONE !>>>>>>>>>>>>>>>>>>>>>>> PUMP 1 <<<<<<<<<<<<<<<<<<<<<<<<<<< data%State%Pump(1)%FlowRatePerSTK = data%Configuration%Pumps%MudPump1VolumetricOutput !.1d0 ![bbl/stk] data%State%Pump(1)%RateChange = data%Configuration%Pumps%MudPump1PumpRateChange ![stk/min2 ??] data%State%Pump(1)%DelayToShutdown = data%Configuration%Pumps%MudPump1DelayToShutdown ![min] data%State%Pump(1)%Mech_Efficiency = data%Configuration%Pumps%MudPump1MechanicalEfficiency ![dimensionless] !data%State%Pump(1)%Vol_Efficiency = MudPump1VolumetricEfficiency !bayad hazf beshe ? data%State%Pump(1)%Max_Pressure = data%Configuration%Pumps%MudPump1MaximumPressure !6000.d0 ![psi] data%State%Pump(1)%MaxSPM = data%Configuration%Pumps%MudPump1Maximum ![spm] data%State%Pump(1)%Trans_Ratio = 965.d0/data%State%Pump(1)%MaxSPM data%State%Pump(1)%time_step = 0.1d0 !?????? niaz hast ya na?? data%State%Pump(1)%RateChange = (data%State%Pump(1)%RateChange*data%State%Pump(1)%Trans_Ratio)/60.d0 ![rpm/s ??] 24/60 data%State%Pump(1)%DelayToShutdown = data%State%Pump(1)%DelayToShutdown/60.d0 ![s] data%State%Pump(1)%K_throttle = 0 data%State%Pump(1)%N_old = 0.d0 Call Pump_OffMode_Solver(1) !>>>>>>>>>>>>>>>>>>>>>>> PUMP 2 <<<<<<<<<<<<<<<<<<<<<<<<<<< data%State%Pump(2)%FlowRatePerSTK = data%Configuration%Pumps%MudPump2VolumetricOutput !.1d0 ![bbl/stk] data%State%Pump(2)%RateChange = data%Configuration%Pumps%MudPump2PumpRateChange ![stk/min2 ??] data%State%Pump(2)%DelayToShutdown = data%Configuration%Pumps%MudPump2DelayToShutdown ![min] data%State%Pump(2)%Mech_Efficiency = data%Configuration%Pumps%MudPump2MechanicalEfficiency ![dimensionless] !data%State%Pump(2)%Vol_Efficiency = MudPump2VolumetricEfficiency !bayad hazf beshe ? data%State%Pump(2)%Max_Pressure = data%Configuration%Pumps%MudPump2MaximumPressure !6000.d0 ![psi] data%State%Pump(2)%MaxSPM = data%Configuration%Pumps%MudPump2Maximum ![spm] data%State%Pump(2)%Trans_Ratio = 965.d0/data%State%Pump(2)%MaxSPM data%State%Pump(2)%time_step = 0.1d0 !?????? niaz hast ya na?? data%State%Pump(2)%RateChange = (data%State%Pump(2)%RateChange*data%State%Pump(2)%Trans_Ratio)/60.d0 ![rpm/s ??] data%State%Pump(2)%DelayToShutdown = data%State%Pump(2)%DelayToShutdown/60.d0 ![s] data%State%Pump(2)%K_throttle = 0 data%State%Pump(2)%N_old = 0.d0 Call Pump_OffMode_Solver(2) !!>>>>>>>>>>>>>>>>>>>>>>> PUMP 3 <<<<<<<<<<<<<<<<<<<<<<<<<<< data%State%Pump(3)%FlowRatePerSTK = data%Configuration%Pumps%CementPumpVolumetricOutput !.1d0 ![bbl/stk] data%State%Pump(3)%RateChange = data%Configuration%Pumps%CementPumpPumpRateChange ![stk/min2 ??] data%State%Pump(3)%DelayToShutdown = data%Configuration%Pumps%CementPumpDelayToShutdown ![min] data%State%Pump(3)%Mech_Efficiency = data%Configuration%Pumps%CementPumpMechanicalEfficiency ![dimensionless] !data%State%Pump(3)%Vol_Efficiency = CementPumpVolumetricEfficiency !bayad hazf beshe ? data%State%Pump(3)%Max_Pressure = data%Configuration%Pumps%CementPumpMaximumPressure !6000.d0 ![psi] data%State%Pump(3)%MaxSPM = data%Configuration%Pumps%CementPumpMaximum ![spm] data%State%Pump(3)%Trans_Ratio = 965.d0/data%State%Pump(3)%MaxSPM data%State%Pump(3)%time_step = 0.1d0 !?????? niaz hast ya na?? data%State%Pump(3)%RateChange = (data%State%Pump(3)%RateChange*data%State%Pump(3)%Trans_Ratio)/60.d0 ![rpm/s ??] data%State%Pump(3)%DelayToShutdown = data%State%Pump(3)%DelayToShutdown/60.d0 ![s] data%State%Pump(3)%K_throttle = 0 data%State%Pump(3)%N_old = 0.d0 Call Pump_OffMode_Solver(3) end subroutine Pumps_StartUp subroutine Pump_OffMode_Solver(Pump_No) use SimulationVariables IMPLICIT NONE INTEGER :: Pump_No data%State%Pump(Pump_No)%N_new = 0.d0 !========================== Pump Rate limit ========================== if (((data%State%Pump(Pump_No)%N_new-data%State%Pump(Pump_No)%N_old)/data%State%Pump(Pump_No)%time_step)>data%State%Pump(Pump_No)%RateChange) then data%State%Pump(Pump_No)%Speed =(data%State%Pump(Pump_No)%RateChange*data%State%Pump(Pump_No)%time_step)+data%State%Pump(Pump_No)%N_old else if (((data%State%Pump(Pump_No)%N_old-data%State%Pump(Pump_No)%N_new)/data%State%Pump(Pump_No)%time_step)>data%State%Pump(Pump_No)%RateChange) then data%State%Pump(Pump_No)%Speed = (-data%State%Pump(Pump_No)%RateChange*data%State%Pump(Pump_No)%time_step)+data%State%Pump(Pump_No)%N_old else data%State%Pump(Pump_No)%Speed = data%State%Pump(Pump_No)%N_new end if !======================================================================= data%State%Pump(Pump_No)%Flow_Rate = data%State%Pump(Pump_No)%FlowRatePerSTK*4118.d0*0.01d0*(data%State%Pump(Pump_No)%Speed/data%State%Pump(Pump_No)%Trans_Ratio) ![gpm] data%State%Pump(Pump_No)%HorsePower = ((data%State%Pump(Pump_No)%Flow_Rate/0.01d0)*data%State%Pump(Pump_No)%StandPipe_Pressure)/(168067.d0*data%State%Pump(Pump_No)%Mech_Efficiency) ![HHP] !data%State%Pump(Pump_No)%Max_Horsepower = ((data%State%Pump(Pump_No)%Flow_Rate/0.01d0)*data%State%Pump(Pump_No)%Max_Pressure)/(168067.d0*data%State%Pump(Pump_No)%Mech_Efficiency) ![HHP] data%State%Pump(Pump_No)%Max_Horsepower = (data%State%Pump(Pump_No)%Flow_Rate*data%State%Pump(Pump_No)%Max_Pressure)/(1714.d0*data%State%Pump(Pump_No)%Mech_Efficiency) if ( data%State%Pump(Pump_No)%StandPipe_Pressure>data%State%Pump(Pump_No)%Max_Pressure ) then ! in shart check shavad !if ( (data%State%Pump(Pump_No)%StandPipe_Pressure*data%State%Pump(Pump_No)%Flow_Rate)>(1714.d0*data%State%Pump(Pump_No)%Max_Horsepower*data%State%Pump(Pump_No)%Mech_Efficiency) ) then data%State%Pump(Pump_No)%Flow_Rate = (1714.d0*data%State%Pump(Pump_No)%Mech_Efficiency*data%State%Pump(Pump_No)%Max_Horsepower)/data%State%Pump(Pump_No)%StandPipe_Pressure ![gpm] data%State%Pump(Pump_No)%Speed = ( data%State%Pump(Pump_No)%Flow_Rate/(data%State%Pump(Pump_No)%FlowRatePerSTK*4118.d0*0.01d0) )*data%State%Pump(Pump_No)%Trans_Ratio ![rpm] end if data%State%Pump(Pump_No)%SoundSPM = INT(data%State%Pump(Pump_No)%Speed/data%State%Pump(Pump_No)%Trans_Ratio) ![SPM] If (data%State%Pump(Pump_No)%Flow_Rate>0.d0) Then data%State%Pump(Pump_No)%Open_Close = 1 Else data%State%Pump(Pump_No)%Open_Close = 0 End if end subroutine Pump_OffMode_Solver subroutine Pump_OnMode_Solver(Pump_No) use SimulationVariables IMPLICIT NONE INTEGER :: Pump_No data%State%Pump(Pump_No)%Flow_Rate = data%State%Pump(Pump_No)%FlowRatePerSTK*4118.d0*0.01d0*(data%State%Pump(Pump_No)%Speed/data%State%Pump(Pump_No)%Trans_Ratio) ![gpm] data%State%Pump(Pump_No)%Max_FlowRate = data%State%Pump(Pump_No)%FlowRatePerSTK*4118.d0*0.01d0*data%State%Pump(Pump_No)%MaxSPM ![gpm] data%State%Pump(Pump_No)%HorsePower = ((data%State%Pump(Pump_No)%Flow_Rate/0.01d0)*data%State%Pump(Pump_No)%StandPipe_Pressure)/(168067.d0*data%State%Pump(Pump_No)%Mech_Efficiency) ![HHP] !data%State%Pump(Pump_No)%Max_Horsepower = ((data%State%Pump(Pump_No)%Flow_Rate/0.01d0)*data%State%Pump(Pump_No)%Max_Pressure)/(168067.d0*data%State%Pump(Pump_No)%Mech_Efficiency) ![HHP] data%State%Pump(Pump_No)%Max_Horsepower = (data%State%Pump(Pump_No)%Flow_Rate*data%State%Pump(Pump_No)%Max_Pressure)/(1714.d0*data%State%Pump(Pump_No)%Mech_Efficiency) if ( data%State%Pump(Pump_No)%StandPipe_Pressure>data%State%Pump(Pump_No)%Max_Pressure ) then ! in shart check shavad !if ( (data%State%Pump(Pump_No)%StandPipe_Pressure*data%State%Pump(Pump_No)%Flow_Rate)>(1714.d0*data%State%Pump(Pump_No)%Max_Horsepower*data%State%Pump(Pump_No)%Mech_Efficiency) ) then data%State%Pump(Pump_No)%Flow_Rate = (1714.d0*data%State%Pump(Pump_No)%Mech_Efficiency*data%State%Pump(Pump_No)%Max_Horsepower)/data%State%Pump(Pump_No)%StandPipe_Pressure ![gpm] data%State%Pump(Pump_No)%Speed = ( data%State%Pump(Pump_No)%Flow_Rate/(data%State%Pump(Pump_No)%FlowRatePerSTK*4118.d0*0.01d0) )*data%State%Pump(Pump_No)%Trans_Ratio ![rpm] end if data%State%Pump(Pump_No)%SoundSPM = INT(data%State%Pump(Pump_No)%Speed/data%State%Pump(Pump_No)%Trans_Ratio) ![SPM] ![spm] If (data%State%Pump(Pump_No)%Flow_Rate>0.d0) Then data%State%Pump(Pump_No)%Open_Close = 1 Else data%State%Pump(Pump_No)%Open_Close = 0 End if end subroutine Pump_OnMode_Solver ! subroutine Pump1_Output ! implicit none ! end subroutine Pump1_Output ! subroutine Pump1MainBody ! use ifport ! use ifmt ! implicit none ! Call Pumps_StartUp ! loop1 : do ! Call Pumps_MainSolver ! 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 CWarnings ! 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 (data%State%Pump(1)%PowerFailMalf==1) then ! ! !! !MP1BLWR=0 ! ! !! Call Pump3_OffMode_Solver ! ! !! Call ClosePump1() ! ! !!end if ! ! ! ! !if( (MP1CPSwitch==1) .and. (MP1Throttle==0.) .and. (data%State%Pump(3)%PowerFailMalf==0) ) then ! !! ! !! loop2: do ! !! ! !! Call DATE_AND_TIME(values=MP_START_TIME) ! !! ! !!!! ! Pump3 Malfunction ----> Power Failure ! !!!! if (data%State%Pump(1)%PowerFailMalf==1) then ! !!!! !MP1BLWR=0 ! !!!! Pump3_OffMode_Solver ! !!!! Call ClosePump1() ! !!!! exit loop2 ! !!!! end if ! !! ! !! data%State%Pump(3)%N_new = MP1Throttle ! !! if (((data%State%Pump(3)%N_new-data%State%Pump(3)%N_old)/data%State%Pump(3)%time_step)>193.) then ! !! data%State%Pump(3)%N_ref =(193.*data%State%Pump(3)%time_step)+data%State%Pump(3)%N_old ! !! else if (((data%State%Pump(3)%N_old-data%State%Pump(3)%N_new)/data%State%Pump(3)%time_step)>193.) then ! !! data%State%Pump(3)%N_ref = (-193.*data%State%Pump(3)%time_step)+data%State%Pump(3)%N_old ! !! else ! !! data%State%Pump(3)%N_ref = data%State%Pump(3)%N_new ! !! end if ! !! ! !! Call Pump3_OnMode_Solver ! !! ! !! IF (data%State%Pump(3)%Flow_Rate>0.) Then ! !! Call OpenCementPump() ! !! Else ! !! Call CloseCementPump() ! !! End if ! !! ! !! data%State%Pump(3)%N_old = data%State%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)) ! !! !if(print_log) 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