SUBROUTINE PIPE_RAMS1 USE VARIABLES ! USE CAccumulatorVariables ! USE CBopStackVariables USE CBopStackVariables USE CBopControlPanelVariables USE CEquipmentsConstants ! ! use CSimulationVariables implicit none !===================================================================== ! PIPE RAMS 1- BOP CAMERON Type U 5000 ! START CONDITIONS FOR PIPE RAMS 1 !===================================================================== RAM(2)%SuccessionCounter = RAM(2)%SuccessionCounter + 1 if (BopControlPanel%UpperRamsValve == 1.0 .and. PipeRam1%UpperRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if (BopStackInput%UpperRamsCloseLEDMine == LedOn) then RETURN end if if ( RAM(2)%SuccessionCounter /= RAM(2)%SuccessionCounterOld+1 ) then RAM(2)%SuccessionCounter = 0 ! also in starup RAM(2)%SuccessionCounterOld = 0 ! also in starup !return else RAM(2)%SuccessionCounterOld= RAM(2)%SuccessionCounter endif if ( RAM(2)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return RAM(2)%First_CloseTimecheck= 1 BopControlPanel%UpperRamsOpenLED = LedOff BopStackInput%UpperRamsOpenLEDMine = LedOff BopControlPanel%UpperRamsCloseLED = LedOn !LedBlinking RAM(2)%FourwayValve = 1 endif endif if (RAM(2)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close !write(*,*) 'close 2' RAM(2)%FourwayValve = 0 PipeRam1%closed=0 !PipeRam1_closed_withPossibility= PipeRam1_closed * TD_BOPConnectionPossibility(2) RAM(2)%vdis_tot=0 RAM(2)%vdis_bottles=0. RAM(2)%fvr_air=0. RAM(2)%vdis_elecp=0. Pumps%Qiter=7 RAM(2)%Qzero=70 RAM(2)%Q=RAM(2)%Qzero RAM(2)%flow=70 RAM(2)%tol=0.0037 if (PipeRam1%finished==1) then PipeRam1%PipeRams1DotLeverOld=-1.0 else PipeRam1%PipeRams1DotLeverOld=BopControlPanel%UpperRamsValve endif PipeRam1%finished=0 PipeRam1%IsClosing = .true. PipeRam1%IsOpening = .false. RAM(2)%bop_type = 3 !AbopPipeRam=196.67 PipeRam1%A=(BopStackSpecification%UpperRamClose*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.) PipeRam1%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-max(PipeRam1%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231) !3.67 galon for each BOP endif if (BopControlPanel%UpperRamsValve == -1.0 .and. PipeRam1%UpperRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if (BopStackInput%UpperRamsOpenLEDMine == LedOn) then RETURN end if if ( RAM(2)%SuccessionCounter /= RAM(2)%SuccessionCounterOld+1 ) then RAM(2)%SuccessionCounter = 0 ! also in starup RAM(2)%SuccessionCounterOld = 0 ! also in starup !return else RAM(2)%SuccessionCounterOld= RAM(2)%SuccessionCounter endif if ( RAM(2)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return RAM(2)%First_OpenTimecheck= 1 BopControlPanel%UpperRamsCloseLED = LedOff !new BopStackInput%UpperRamsCloseLEDMine = LedOff !new BopControlPanel%UpperRamsOpenLED = LedOn !LedBlinking RAM(2)%FourwayValve = 1 endif endif if (RAM(2)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close !write(*,*) 'open 2' RAM(2)%FourwayValve = 0 PipeRam1%closed=0 !PipeRam1_closed_withPossibility= PipeRam1_closed * TD_BOPConnectionPossibility(2) RAM(2)%vdis_tot=0 RAM(2)%vdis_bottles=0. RAM(2)%fvr_air=0. RAM(2)%vdis_elecp=0. Pumps%Qiter=7 RAM(2)%Qzero=70 RAM(2)%Q=RAM(2)%Qzero RAM(2)%flow=70 RAM(2)%tol=0.0037 if (PipeRam1%finished==1) then PipeRam1%PipeRams1DotLeverOld=1.0 else PipeRam1%PipeRams1DotLeverOld=BopControlPanel%UpperRamsValve endif PipeRam1%finished=0 PipeRam1%IsOpening = .true. PipeRam1%IsClosing = .false. !if (UpperRamsOpenLED == LedOn) then ! RETURN !end if RAM(2)%bop_type = 3 !AbopPipeRam=186.5 PipeRam1%A=(BopStackSpecification%UpperRamOpen*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.) PipeRam1%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-max(PipeRam1%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231) !3.48 galon for each BOP endif !===================================================================== Annular%FirstSet= 0 AnnularComputational%RamsFirstSet= 0 if (PipeRam1%IsOpening .or. PipeRam1%IsClosing .or. RAM(2)%Bottles_Charged_MalfActive) then Annular%FirstSet= 0 AnnularComputational%RamsFirstSet= 0 CALL PIPE_RAMS1_SUB end if END SUBROUTINE PIPE_RAMS1 SUBROUTINE PIPE_RAMS1_SUB USE VARIABLES USE CBopStackVariables USE CBopControlPanelVariables USE CEquipmentsConstants ! use CSimulationVariables implicit none ! FirstSet= 0 ! RamsFirstSet= 0 ! loop3: do while (finished_pipe1==0) RAM(2)%SuccessionCounter = RAM(2)%SuccessionCounter + 1 if (BopControlPanel%UpperRamsValve == 1.0 .and. PipeRam1%PipeRams1DotLeverOld == -1.0 .and. PipeRam1%UpperRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if ( RAM(2)%First_CloseTimecheck == 0 ) then if ( RAM(2)%SuccessionCounter /= RAM(2)%SuccessionCounterOld+1 ) then RAM(2)%SuccessionCounter = 0 ! also in starup RAM(2)%SuccessionCounterOld = 0 ! also in starup !return else RAM(2)%SuccessionCounterOld= RAM(2)%SuccessionCounter endif if ( RAM(2)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return BopControlPanel%UpperRamsOpenLED = LedOff BopStackInput%UpperRamsOpenLEDMine = LedOff BopControlPanel%UpperRamsCloseLED = LedOn !LedBlinking RAM(2)%FourwayValve = 1 endif endif endif if (RAM(2)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then !write(*,*) 'close 4' RAM(2)%FourwayValve = 0 PipeRam1%closed=0 !PipeRam1_closed_withPossibility= PipeRam1_closed * TD_BOPConnectionPossibility(2) ! for TD code CALL OpenUpperRams ! for C code PipeRam1%Situation_forTD= 0 ! open - for TD code RAM(2)%p_bop=ShearRam%PA PipeRam1%PipeRams1DotLeverOld = BopControlPanel%UpperRamsValve RAM(2)%bop_type = 3 !AbopPipeRam=196.67 PipeRam1%A=(BopStackSpecification%UpperRamClose*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.) !write(*,*) 'NeededVolumeShearRams1=',NeededVolumeShearRams PipeRam1%NeededVolume=PipeRam1%A*(PipeRam1%ID-max(PipeRam1%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231) ! write(*,*) 'NeededVolumeShearRams2=',NeededVolumeShearRams RAM(2)%vdis_bottles=0. RAM(2)%fvr_air=0. RAM(2)%vdis_elecp=0. PipeRam1%IsClosing = .true. PipeRam1%IsOpening = .false. endif if (BopControlPanel%UpperRamsValve == -1.0 .and. PipeRam1%PipeRams1DotLeverOld == 1.0 .and. PipeRam1%UpperRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if ( RAM(2)%First_OpenTimecheck == 0 ) then if ( RAM(2)%SuccessionCounter /= RAM(2)%SuccessionCounterOld+1 ) then RAM(2)%SuccessionCounter = 0 ! also in starup RAM(2)%SuccessionCounterOld = 0 ! also in starup !return else RAM(2)%SuccessionCounterOld= RAM(2)%SuccessionCounter endif if ( RAM(2)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return BopControlPanel%UpperRamsCloseLED = LedOff BopStackInput%UpperRamsCloseLEDMine = LedOff BopControlPanel%UpperRamsOpenLED = LedOn !LedBlinking RAM(2)%FourwayValve = 1 endif endif endif if (RAM(2)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then !write(*,*) 'open 4' RAM(2)%FourwayValve = 0 PipeRam1%closed=0 !PipeRam1_closed_withPossibility= PipeRam1_closed * TD_BOPConnectionPossibility(2) CALL OpenUpperRams PipeRam1%Situation_forTD= 0 ! open - for TD code RAM(2)%p_bop=ShearRam%PA PipeRam1%PipeRams1DotLeverOld = BopControlPanel%UpperRamsValve RAM(2)%bop_type = 3 !AbopPipeRam=186.5 PipeRam1%A=(BopStackSpecification%UpperRamOpen*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.) PipeRam1%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-PipeRam1%ID)/(2.*231) RAM(2)%vdis_bottles=0. RAM(2)%fvr_air=0. RAM(2)%vdis_elecp=0. PipeRam1%IsOpening = .true. PipeRam1%IsClosing = .false. endif RAM(2)%First_CloseTimecheck = 0 RAM(2)%First_OpenTimecheck = 0 RAM(2)%time=RAM(2)%time+RamLine%DeltaT_BOP !overal time (s) !=================================================== ! BOP !=================================================== if (PipeRam1%closed==0) then !bop closing call bop_code(2,PipeRam1%H,2) !ramtype=2 2=RNUMBER endif !bop is closing !================================================================ if (PipeRam1%closed==1) then RAM(2)%Q=0 !p_bop=pram_reg RAM(2)%p_bop=ShearRam%PA RAMS%minloss(2,17)=0. !RNUMBER=2 endif RAM(2)%timecounter_ram=RAM(2)%timecounter_ram+1 ! MiddleRamsStatus = IDshearBop ! UpperRamsStatus = IDPipeRam1 ! LowerRamsStatus = IDPipeRam2 ! AnnularStatus = IDAnnular ! AccumulatorPressureGauge = p_acc ! ManifoldPressureGauge= pram_reg ! AnnularPressureGauge=Pannular_reg ! ! ! ! WRITE(60,60) RAM(2)%time,RAM(2)%Q,RAM(2)%vdis_tot,p_acc, & ! pram_reg,Pannular_reg,RAM(2)%p_bop,IDshearBop, & ! IDPipeRam1,IDPipeRam2,IDAnnular !60 FORMAT(11(f18.5)) ! call sleepqq(100) if (PipeRam1%closed==1) then ! if ((MiddleRamsValve==1. .and. MiddleRamsFailureMalf==0) .or. (MiddleRamsValve==-1.0 .and. MiddleRamsFailureMalf==0) .or. (LowerRamsValve==1. .and. LowerRamsFailureMalf==0) .or. (LowerRamsValve==-1.0 .and. LowerRamsFailureMalf==0) .or. (AnnularValve==1. .and. AnnularFailureMalf==0) .or. (AnnularValve==-1.0 .and. AnnularFailureMalf==0) .or. ChokeLineValve==1. .or. ChokeLineValve==-1.0 .or. KillLineValve==1. .or. KillLineValve==-1.0) then PipeRam1%finished=1 ! endif endif ! if (IsStopped == .true.) return ! end do loop3 !while finished_pipe1==0 if ( PipeRam1%finished==1 .and. RAM(2)%Bottles_Charged_MalfActive==.true.) then call bop_code(2,PipeRam1%H,2) !ramtype=2 2=RNUMBER ! call sleepqq(100) endif END SUBROUTINE PIPE_RAMS1_SUB