|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308 |
-
-
- SUBROUTINE KILL_LINE
- USE VARIABLES
- USE CAccumulatorVariables
- USE CBopStackVariables
- USE CBopControlPanelVariables
- USE CEquipmentsConstants
- ! use CSimulationVariables
-
- implicit none
-
-
- !=====================================================================
- ! KILL LINE 1- BOP CAMERON Type U 5000
- ! START CONDITIONS FOR KILL LINE 1
- !=====================================================================
-
- RAM(6)%SuccessionCounter = RAM(6)%SuccessionCounter + 1
-
-
- if (BopControlPanel%KillLineValve == -1.0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then
-
- if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
- RAM(6)%SuccessionCounter = 0 ! also in starup
- RAM(6)%SuccessionCounterOld = 0 ! also in starup
- return
- else
- RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
- endif
-
-
- if ( RAM(6)%SuccessionCounter < int(2.5/RamLine%DeltaT_BOP) ) then
- return
- endif
-
- RAM(6)%First_CloseTimecheck= 1
-
-
-
- if (BopStackInput%KillLineOpenLedMine == LedOn) then
- RETURN
- end if
- KillLine%closed=0
- RAM(6)%vdis_tot=0
- RAM(6)%vdis_bottles=0.
- RAM(6)%fvr_air=0.
- RAM(6)%vdis_elecp=0.
- Pumps%Qiter=7
- RAM(6)%Qzero=70
- RAM(6)%Q=RAM(6)%Qzero
- RAM(6)%flow=70
- RAM(6)%tol=0.0037
- if (KillLine%finished==1) then
- KillLine%LeverOld= 1.0
- else
- KillLine%LeverOld=BopControlPanel%KillLineValve
- endif
- KillLine%finished=0
- KillLine%IsOpening = .true.
- BopControlPanel%KillLineCloseLED = LedOff
- BopStackInput%KillLineCloseLedMine = LedOff
- BopControlPanel%KillLineOpenLED = LedOn !LedBlinking
- RAM(6)%bop_type = 3
- !AbopKillLine=196.67
- KillLine%Abop=(BopStackSpecification%KillClose*231)/((KillLine%IDBase-KillLine%ODDrillpipe_inBase)/2.)
- KillLine%NeededVolume=KillLine%Abop*(KillLine%IDBase-max(KillLine%ODDrillpipe_in,KillLine%ODDrillpipe_inBase))/(2.*231) !1.5 galon for each BOP
- endif
-
- if (BopControlPanel%KillLineValve == 1.0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then
-
-
- if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
- RAM(6)%SuccessionCounter = 0 ! also in starup
- RAM(6)%SuccessionCounterOld = 0 ! also in starup
- return
- else
- RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
- endif
-
-
- if ( RAM(6)%SuccessionCounter < int(2.5/RamLine%DeltaT_BOP) ) then
- return
- endif
-
- RAM(6)%First_OpenTimecheck= 1
-
-
-
- if (BopStackInput%KillLineCloseLedMine == LedOn) then
- RETURN
- end if
- KillLine%closed=0
- RAM(6)%vdis_tot=0
- RAM(6)%vdis_bottles=0.
- RAM(6)%fvr_air=0.
- RAM(6)%vdis_elecp=0.
- Pumps%Qiter=7
- RAM(6)%Qzero=70
- RAM(6)%Q=RAM(6)%Qzero
- RAM(6)%flow=70
- RAM(6)%tol=0.0037
-
-
-
- if (KillLine%finished==1) then
- KillLine%LeverOld= -1.0
- else
- KillLine%LeverOld=BopControlPanel%KillLineValve
- endif
- KillLine%finished=0
- KillLine%IsClosing = .true.
-
-
- !if (KillLineCloseLed == LedOn) then
- ! RETURN
- !end if
-
- BopControlPanel%KillLineCloseLED = LedOff !new
- BopStackInput%KillLineCloseLedMine = LedOff !new
-
- BopControlPanel%KillLineCloseLED = LedOn !LedBlinking
- RAM(6)%bop_type = 3
- !AbopKillLine=196.67
- KillLine%Abop=(BopStackSpecification%KillOpen*231)/((KillLine%IDBase-KillLine%ODDrillpipe_inBase)/2.)
- KillLine%NeededVolume=KillLine%Abop*(KillLine%IDBase-max(KillLine%ODDrillpipe_in,KillLine%ODDrillpipe_inBase))/(2.*231) !1.5 galon for each BOP
- endif
-
- !==========================================================================
-
- if (KillLine%IsOpening .or. KillLine%IsClosing) then
- CALL KILL_LINE_SUB
- end if
-
-
- END SUBROUTINE KILL_LINE
-
-
-
-
-
-
-
-
-
-
-
- SUBROUTINE KILL_LINE_SUB
-
- USE VARIABLES
- USE CAccumulatorVariables
- USE CBopStackVariables
- USE CBopControlPanelVariables
- USE CEquipmentsConstants
- ! use CSimulationVariables
-
- implicit none
-
-
- Annular%FirstSet= 0
- AnnularComputational%RamsFirstSet= 0
-
- ! loop6: do while (finished_KillLine==0)
-
-
- RAM(6)%SuccessionCounter = RAM(6)%SuccessionCounter + 1
-
-
-
- if (BopControlPanel%KillLineValve == 1.0 .and. KillLine%LeverOld == -1.0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then
-
- if ( RAM(6)%First_CloseTimecheck == 0 ) then
-
-
- if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
- RAM(6)%SuccessionCounter = 0 ! also in starup
- RAM(6)%SuccessionCounterOld = 0 ! also in starup
- return
- else
- RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
- endif
-
-
-
- if ( RAM(6)%SuccessionCounter < int(2.5/RamLine%DeltaT_BOP) ) then
- return
- endif
-
- endif
-
-
-
- KillLine%closed=0
- RAM(6)%p_bop=ShearRam%PA
- KillLine%LeverOld = BopControlPanel%KillLineValve
- BopControlPanel%KillLineOpenLED = LedOff
- BopStackInput%KillLineOpenLedMine = LedOff
- BopControlPanel%KillLineCloseLED = LedOn !LedBlinking
- CALL OpenKillLine
- RAM(6)%bop_type = 3
- !AbopKillLine=196.67
- KillLine%Abop=(BopStackSpecification%KillClose*231)/((KillLine%IDBase-KillLine%ODDrillpipe_inBase)/2.)
- KillLine%NeededVolume=KillLine%Abop*(KillLine%ID-max(KillLine%ODDrillpipe_in,KillLine%ODDrillpipe_inBase))/(2.*231)
-
- RAM(6)%vdis_bottles=0.
- RAM(6)%fvr_air=0.
- RAM(6)%vdis_elecp=0.
- KillLine%IsClosing = .true.
- KillLine%IsOpening = .false.
- endif
-
- if (BopControlPanel%KillLineValve == -1.0 .and. KillLine%LeverOld == 1.0 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then
-
-
- if ( RAM(6)%First_OpenTimecheck == 0 ) then
-
- if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
- RAM(6)%SuccessionCounter = 0 ! also in starup
- RAM(6)%SuccessionCounterOld = 0 ! also in starup
- return
- else
- RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
- endif
-
- if ( RAM(6)%SuccessionCounter < int(2.5/RamLine%DeltaT_BOP) ) then
- return
- endif
-
- endif
-
-
- KillLine%closed=0
- RAM(6)%p_bop=ShearRam%PA
- KillLine%LeverOld = BopControlPanel%KillLineValve
- BopControlPanel%KillLineCloseLED = LedOff
- BopStackInput%KillLineCloseLedMine = LedOff
- BopControlPanel%KillLineOpenLED = LedOn !LedBlinking
- CALL OpenKillLine
- RAM(6)%bop_type = 3
- !AbopKillLine=196.67
- KillLine%Abop=(BopStackSpecification%KillOpen*231)/((KillLine%IDBase-KillLine%ODDrillpipe_inBase)/2.)
- KillLine%NeededVolume=KillLine%Abop*(KillLine%IDBase-KillLine%ID)/(2.*231)
- RAM(6)%vdis_bottles=0.
- RAM(6)%fvr_air=0.
- RAM(6)%vdis_elecp=0.
-
- KillLine%IsOpening = .true.
- KillLine%IsClosing = .false.
- endif
-
-
- RAM(6)%First_CloseTimecheck = 0
- RAM(6)%First_OpenTimecheck = 0
-
-
- RAM(6)%time=RAM(6)%time+RamLine%DeltaT_BOP !overal time (s)
-
-
-
- !===================================================
- ! BOP
- !===================================================
- if (KillLine%closed==0) then !bop closing
- call bop_code(5,KillLine%H_Bop,6) !ramtype=5 6=RNUMBER
- endif !bop is closing
- !================================================================
- if (KillLine%closed==1) then
- RAM(6)%Q=0
- !p_bop=pram_reg
- RAM(6)%p_bop=ShearRam%PA
- RAMS%minloss(6,17)=0. !RNUMBER=6
- endif
-
- RAM(6)%timecounter_ram=RAM(6)%timecounter_ram+1
-
-
-
-
-
- ! MiddleRamsStatus = IDshearBop
- ! UpperRamsStatus = IDPipeRam1
- ! LowerRamsStatus = IDPipeRam2
- ! AnnularStatus = IDAnnular
- ! AccumulatorPressureGauge = p_acc
- ! ManifoldPressureGauge= pram_reg
- ! AnnularPressureGauge=Pannular_reg
- !
- !
- !
- ! WRITE(60,60) RAM(6)%time,RAM(6)%Q,RAM(6)%vdis_tot,p_acc, &
- ! pram_reg,Pannular_reg,RAM(6)%p_bop,IDshearBop, &
- ! IDPipeRam1,IDPipeRam2,IDAnnular
- !60 FORMAT(11(f18.5))
-
-
- ! call sleepqq(100)
-
- if (KillLine%closed==1) then
- ! if ((UpperRamsValve==1. .and. UpperRamsFailureMalf==0) .or. (UpperRamsValve==-1.0 .and. UpperRamsFailureMalf==0) .or. (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) then
- KillLine%finished=1
- ! endif
- endif
-
- ! if (IsStopped == .true.) return
-
- ! end do loop6 !while finished_KillLine==0
-
- END SUBROUTINE KILL_LINE_SUB
|