SUBROUTINE SHEAR_RAMS USE VARIABLES USE CBopStackVariables USE CBopControlPanelVariables USE CEquipmentsConstants ! use CSimulationVariables implicit none !===================================================================== ! SHEAR RAMS- BOP CAMERON Type U 5000 ! START CONDITIONS FOR SHEAR RAMS !===================================================================== RAM(4)%SuccessionCounter = RAM(4)%SuccessionCounter + 1 if (BopControlPanel%MiddleRamsValve == 1.0 .and. ShearRam%MiddleRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if (BopStackInput%MiddleRamsCloseLEDMine == LedOn) then RETURN end if if ( RAM(4)%SuccessionCounter /= RAM(4)%SuccessionCounterOld+1 ) then RAM(4)%SuccessionCounter = 0 ! also in starup RAM(4)%SuccessionCounterOld = 0 ! also in starup !return else RAM(4)%SuccessionCounterOld= RAM(4)%SuccessionCounter endif if ( RAM(4)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return RAM(4)%First_CloseTimecheck= 1 BopControlPanel%MiddleRamsOpenLED = LedOff BopStackInput%MiddleRamsOpenLEDMine = LedOff BopControlPanel%MiddleRamsCloseLED = LedOn !LedBlinking RAM(4)%FourwayValve = 1 endif endif if (RAM(4)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close !write(*,*) 'close 2' RAM(4)%FourwayValve = 0 RamLine%ShearBop_closed=0 !ShearBop_closed_withPossibility= ShearBop_closed * TD_BOPConnectionPossibility(3) RAM(4)%vdis_tot=0 RAM(4)%vdis_bottles=0. RAM(4)%fvr_air=0. RAM(4)%vdis_elecp=0. Pumps%Qiter=7 RAM(4)%Qzero=70 RAM(4)%Q=RAM(4)%Qzero RAM(4)%flow=70 RAM(4)%tol=0.0037 if (RamLine%FINISHED_shear==1) then RamLine%ShearRamsLeverOld=-1.0 else RamLine%ShearRamsLeverOld=BopControlPanel%MiddleRamsValve endif RamLine%FINISHED_shear=0 RamLine%ShearRamIsClosing = .true. RamLine%ShearRamIsOpening = .false. RAM(4)%bop_type = 2 !NeededVolumeShearRams=5.8 !galon for each BOP !AbopShearRam=196.67 !(in^2) ShearRam%AbopShearRam=(BopStackSpecification%BlindRamClose*231)/(ShearRam%IDshearBopBase/2.) !NeededVolumeShearRams=BlindRamClose !galon for each BOP **changed ShearRam%NeededVolumeShearRams=ShearRam%AbopShearRam*(ShearRam%IDshearBopBase-ShearRam%ShearIsNotAllowed*ShearRam%ODDrillpipe_inShearRam)/(2.*231) !3.67 galon for each BOP ! **changed ShearRam%VA=ShearRam%AbopShearRam*(ShearRam%IDshearBopBase-ShearRam%ODDrillpipe_inShearRam)/(2.*231) ShearRam%VB=ShearRam%NeededVolumeShearRams endif if (BopControlPanel%MiddleRamsValve == -1.0 .and. ShearRam%MiddleRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then if (BopStackInput%MiddleRamsOpenLEDMine == LedOn) then RETURN end if if ( RAM(4)%SuccessionCounter /= RAM(4)%SuccessionCounterOld+1 ) then RAM(4)%SuccessionCounter = 0 ! also in starup RAM(4)%SuccessionCounterOld = 0 ! also in starup !return else RAM(4)%SuccessionCounterOld= RAM(4)%SuccessionCounter endif if ( RAM(4)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then !return RAM(4)%First_OpenTimecheck= 1 BopControlPanel%MiddleRamsCloseLED = LedOff !new BopStackInput%MiddleRamsCloseLEDMine = LedOff !new BopControlPanel%MiddleRamsOpenLED = LedOn !LedBlinking endif endif if (RAM(4)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close !write(*,*) 'open 2' RAM(4)%FourwayValve = 0 RamLine%ShearBop_closed=0 !ShearBop_closed_withPossibility= ShearBop_closed * TD_BOPConnectionPossibility(3) RAM(4)%vdis_tot=0 RAM(4)%vdis_bottles=0. RAM(4)%fvr_air=0. RAM(4)%vdis_elecp=0. Pumps%Qiter=7 RAM(4)%Qzero=70 RAM(4)%Q=RAM(4)%Qzero RAM(4)%flow=70 RAM(4)%tol=0.0037 if (RamLine%FINISHED_shear==1) then RamLine%ShearRamsLeverOld=1.0 else RamLine%ShearRamsLeverOld=BopControlPanel%MiddleRamsValve endif RamLine%FINISHED_shear=0 RamLine%ShearRamIsOpening = .true. RamLine%ShearRamIsClosing = .false. RAM(4)%bop_type = 3 !AbopShearRam=186.5 !(in^2) ShearRam%AbopShearRam=(BopStackSpecification%BlindRamOpen*231)/(ShearRam%IDshearBopBase/2.) !NeededVolumeShearRams=5.5 !galon for each BOP !NeededVolumeShearRams=BlindRamOpen ! **changed ShearRam%NeededVolumeShearRams=ShearRam%AbopShearRam*(ShearRam%IDshearBopBase-ShearRam%ShearIsNotAllowed*ShearRam%ODDrillpipe_inShearRam)/(2.*231) !3.67 galon for each BOP ! **changed !va=AbopShearRam*(IDshearBopBase-ODDrillpipe_inShearRam)/(2.*231) !vb=NeededVolumeShearRams endif !===================================================================== ! if (ShearRamIsOpening .or. ShearRamIsClosing .or. RAM(4)%Bottles_Charged_MalfActive) then ! CALL SHEAR_RAMS_SUB ! end if END SUBROUTINE SHEAR_RAMS SUBROUTINE SHEAR_RAMS_SUB USE VARIABLES USE CBopStackVariables USE CBopControlPanelVariables USE CEquipmentsConstants ! use CSimulationVariables implicit none ! FirstSet= 0 ! RamsFirstSet= 0 ! loop2: do while (finished_shear==0) RAM(4)%SuccessionCounter = RAM(4)%SuccessionCounter + 1 if (BopControlPanel%MiddleRamsValve == 1.0 .and. RamLine%ShearRamsLeverOld == -1.0 .and. ShearRam%MiddleRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1 .and. RAM(4)%First_CloseTimecheck == 0) then if ( RAM(4)%SuccessionCounter /= RAM(4)%SuccessionCounterOld+1 ) then RAM(4)%SuccessionCounter = 0 ! also in starup RAM(4)%SuccessionCounterOld = 0 ! also in starup else RAM(4)%SuccessionCounterOld= RAM(4)%SuccessionCounter endif if ( RAM(4)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then BopControlPanel%MiddleRamsOpenLED = LedOff BopStackInput%MiddleRamsOpenLEDMine = LedOff BopControlPanel%MiddleRamsCloseLED = LedOn !LedBlinking RAM(4)%FourwayValve = 1 endif endif if (RAM(4)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then RAM(4)%FourwayValve = 0 RamLine%ShearBop_closed=0 RAM(4)%p_bop=ShearRam%PA RamLine%ShearRamsLeverOld = BopControlPanel%MiddleRamsValve CALL OpenMiddleRams ! for C code RamLine%ShearBop_Situation_forTD= 0 ! open - for TD code RAM(4)%bop_type = 2 ShearRam%AbopShearRam=(BopStackSpecification%BlindRamClose*231)/(ShearRam%IDshearBopBase/2.) ShearRam%NeededVolumeShearRams=ShearRam%AbopShearRam*(ShearRam%IDshearBop-ShearRam%ShearIsNotAllowed*ShearRam%ODDrillpipe_inShearRam)/(2.*231) ! **changed RAM(4)%vdis_bottles=0. RAM(4)%fvr_air=0. RAM(4)%vdis_elecp=0. RamLine%ShearRamIsClosing = .true. RamLine%ShearRamIsOpening = .false. endif if (BopControlPanel%MiddleRamsValve == -1.0 .and. RamLine%ShearRamsLeverOld == 1.0 .and. ShearRam%MiddleRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1 .and. RAM(4)%First_OpenTimecheck == 0) then if ( RAM(4)%SuccessionCounter /= RAM(4)%SuccessionCounterOld+1 ) then RAM(4)%SuccessionCounter = 0 ! also in starup RAM(4)%SuccessionCounterOld = 0 ! also in starup !return else RAM(4)%SuccessionCounterOld= RAM(4)%SuccessionCounter endif if ( RAM(4)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then BopControlPanel%MiddleRamsCloseLED = LedOff BopStackInput%MiddleRamsCloseLEDMine = LedOff BopControlPanel%MiddleRamsOpenLED = LedOn !LedBlinking RAM(4)%FourwayValve = 1 endif endif if (RAM(4)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then RAM(4)%FourwayValve = 0 RamLine%ShearBop_closed=0 RAM(4)%p_bop=ShearRam%PA RamLine%ShearRamsLeverOld = BopControlPanel%MiddleRamsValve CALL OpenMiddleRams RamLine%ShearBop_Situation_forTD= 0 ! open - for TD code RAM(4)%bop_type = 3 ShearRam%NeededVolumeShearRams=ShearRam%AbopShearRam*(ShearRam%IDshearBopBase-ShearRam%IDshearBop)/(2.*231) RAM(4)%vdis_bottles=0. RAM(4)%fvr_air=0. RAM(4)%vdis_elecp=0. RamLine%ShearRamIsOpening = .true. RamLine%ShearRamIsClosing = .false. endif RAM(4)%First_CloseTimecheck = 0 RAM(4)%First_OpenTimecheck = 0 RAM(4)%time=RAM(4)%time+RamLine%DeltaT_BOP !overal time (s) !=================================================== ! BOP !=================================================== if (RamLine%ShearBop_closed==0) then !bop closing call bop_code(1,ShearRam%H_ShearRamBop,4) !ramtype=1 4=RNUMBER endif !bop is closing !================================================================ if (RamLine%ShearBop_closed==1) then RAM(4)%Q=0 RAM(4)%p_bop=ShearRam%PA RAMS%minloss(4,17)=0. !RNUMBER=4 endif RAM(4)%timecounter_ram=RAM(4)%timecounter_ram+1 call sleepqq(100) if (RamLine%ShearBop_closed==1) then RamLine%FINISHED_shear=1 endif ! if (IsStopped == .true.) return ! end do loop2 !while finished_shear==0 ! if ( finished_shear==1 .and. RAM(4)%Bottles_Charged_MalfActive==.true.) then ! call bop_code(1,H_ShearRamBop,4) !ramtype=1 4=RNUMBER ! call sleepqq(100) ! endif END SUBROUTINE SHEAR_RAMS_SUB