SUBROUTINE BOP_StartUp() USE VARIABLES USE CAccumulatorVariables USE CBopStackVariables USE CBopControlPanelVariables USE CEquipmentsConstants implicit none integer i !UpperRamsFailureMalf=0 !AnnularFailureMalf=0 !LowerRamsFailureMalf=0 !MiddleRamsFailureMalf=0 !UpperRamsLeakMalf=0 !LowerRamsLeakMalf=0 !MiddleRamsLeakMalf=0 !AnnularLeakMalf=0 !AccPupmsFailMalf=0 !AirSupplyPressureGauge=0 !======================= SETTING VARIABLES BOP_timeCounter= 0 !============== FOR MANIFOLD VALVES CODE===================== CALL OpenAnnular CALL OpenUpperRams CALL OpenMiddleRams CALL CloseKillLine CALL CloseChokeLine CALL OpenLowerRams Annular_Situation_forTD= 0 ! open - for TD code ShearBop_Situation_forTD= 0 ! open - for TD code PipeRam1_Situation_forTD= 0 ! open - for TD code PipeRam2_Situation_forTD= 0 ! open - for TD code !====================================================================== CALL LOSS_INPUTS() ! !OPEN(50,FILE='AIRPUMP_OUTPUTS.DAT') !OPEN(60,FILE='RAMS_OUTPUTS.DAT') !====================================================================== ! GET INPUTS !====================================================================== RAM%SuccessionCounter = 0 RAM%SuccessionCounterOld = 0 RAM%First_CloseTimecheck= 0 RAM%First_OpenTimecheck= 0 Cumulative_AirVolume= 0.0 bottle_capacity=10 !(GALON) nobottles=Accumulator%NumberOfBottels !fvr_tot=40 !(GALON) IN CHARGED POSITION prams_regset=1500 !RamsReglatorSet !=1500 DEFAULT regulator set pressure (PSI) acc_ChargedPressure=3000 !charged(PSI) acc_MinPressure=Accumulator%AccumulatorMinimumOperatingPressure !1200 !discharged(PSI) !acc_precharge=1000 fvr_tot=(-2451*(acc_ChargedPressure**(-0.8202))+8.435)*nobottles ! IT IS WRRITEN FOR PRECHARGE 1000 PSI FROM ITS CURVE !write(*,*) 'fvr_tot=',fvr_tot !ELECTRIC_PUMPON=2800 ELECTRIC_PUMPON=Accumulator%StartPressure !ELECTRIC_PUMPOFF=acc_ChargedPressure !=3000 psi ELECTRIC_PUMPOFF=Accumulator%StopPressure !QELECTRIC_PUMP=12 !(gpm) QELECTRIC_PUMP=Accumulator%ElectricPumpOutput !AIR_PUMPON=2600 AIR_PUMPON=Accumulator%StartPressure2 !AIR_PUMPOFF=2900 AIR_PUMPOFF=Accumulator%StopPressure2 RAM%tol=0.0037 !%=(2700-2600)/2700 RAM%tolzero=RAM%tol tolAnnular=0.0018 !=(2900-2895)/2900 tolzeroAnnular=tolAnnular !======================OTHER INPUTS(CONSTANTS)=========================== pa=300 !(PSI) p_shear=1200 !(PSI) !p_shear=2423.1 !(PSI) pb=p_shear-pa pa_annular=100 !(psi) IDAnnularBase=13.625 !(inch) IDAnnular=IDAnnularBase ODDrillpipe_inAnnularBase=5. ! so 18 gal is for complete closing of annular ODDrillpipe_inAnnular=5. ! initial AnnularMovingPressure=360. !(psi) IDAnnularFinal= IDAnnular IDshearBopBase=13.625 !(inch) IDshearBop=IDshearBopBase ODDrillpipe_inShearRamBase=5 !initial ODDrillpipe_inShearRam=5 !initial IDshearBopFinal= IDshearBop IDPipeRamBase=13.625 !(inch) IDPipeRam1=IDPipeRamBase ODDrillpipe_inPipeRam1Base=5 !initial ODDrillpipe_inPipeRam1=5 !initial IDPipeRam1Final= IDPipeRam1 IDPipeRam2=IDPipeRamBase !(inch) ODDrillpipe_inPipeRam2Base=5 !initial ODDrillpipe_inPipeRam2=5 !initial IDPipeRam2Final= IDPipeRam2 IDChokeLineBase=8.6 !(inch) IDChokeLine=IDChokeLineBase ODDrillpipe_inChokeLineBase=5 ODDrillpipe_inChokeLine=5 IDKillLineBase=8.6 !(inch) IDKillLine=IDKillLineBase ODDrillpipe_inKillLineBase=5 ODDrillpipe_inKillLine=5 !va=4 !(liter) !vb=8 !(liter) !cv=2; !flow coefficinet of regulator RAM_COURSE=320.2 !milimeter H_REGRAM=0 !(m)<<<<<<<<<<<<<<<<<<<<<<<< H_ShearRamBop=(BopStackSpecification%GroundLevel-BopStackSpecification%BlindRamHeight)*0.3048 ! foot to meter H_PipeRam1Bop=(BopStackSpecification%GroundLevel-BopStackSpecification%UpperRamHeight)*0.3048 ! foot to meter H_PipeRam2Bop=(BopStackSpecification%GroundLevel-BopStackSpecification%LowerRamHeight)*0.3048 ! foot to meter H_AnnularBop=(BopStackSpecification%GroundLevel-BopStackSpecification%AnnularPreventerHeight)*0.3048 ! foot to meter H_ChokeLineBop=(BopStackSpecification%GroundLevel-BopStackSpecification%KillHeight)*0.3048 ! foot to meter H_KillLineBop=(BopStackSpecification%GroundLevel-BopStackSpecification%KillHeight)*0.3048 ! foot to meter p_acc=acc_ChargedPressure RAM%vdis_bottles=0 !initial discharged volume fvr=fvr_tot RAMS%minloss=0. !======================AIRPUMP INPUTS(CONSTANTS)=========================== RAM%FVR_AIR=0 P_AIRP=0 ba1=1003; ba2=.03375; ba3=4.014; ba4=.2458 bba1 =31.8; bba2 =-725.7 ; bba3 =4154 Qiter=7 !(gpm) ! Q=0.0003585; true DeltaT_BOP=0.1 !second tol_air=.08 alpha_Qair=0 alpha_timeair=0 alpha_paccair=p_acc alpha_pairp=p_acc alpha_diffpair=0 alpha_lossesair=0 alpha_fvrair=0 counter_airp=1 !======================BOP INPUTS(CONSTANTS)=========================== if (Accumulator%PrechargePressure == 1400.) then b1=1396; b2=0.17; b3=3.873; b4=1.101 elseif (Accumulator%PrechargePressure == 2000.) then b1=1980; b2=0.1237; b3=15.69; b4=1.029 elseif (Accumulator%PrechargePressure == 600.) then b1=591.9; b2=0.1968; b3=2.887; b4=0.9757 else !(PrechargePressure == 1000.) then ! this is for precharge=1000 psi b1=993.7; b2=0.164; b3=5.492; b4=0.9796 endif ByPassOld= 1.0 RAM%p_bop=pa p_annular=pa_annular !Q=0.0055; !initial flow rate (m^3/s) RAM%flow=60 !(gpm) initial value RAM%Qzero=70 !for DP code, increasing Q after shear RAM%vdis_tot=0 airp_switch=0 !off position elecp_switch=0 !off position ShearBop_closed=1 PipeRam1_closed=1 PipeRam2_closed=1 ChokeLine_closed=1 KillLine_closed=1 Annular_closed=1 finished_Shear=0 finished_pipe1=0 finished_pipe2=0 finished_ChokeLine=0 finished_KillLine=0 finished_Annular=0 deltav_elecp=0 RAM%vdis_elecp=0 !================================================================== RAM%timecounter_ram=0 RAM%Q=0 pram_reg=prams_regset !psi !RamsReglatorSet Pannular_reg=min(BopControlPanel%AnnularRegulatorSetControl,1700.) BopControlPanel%MiddleRamsStatus= IDshearBop BopControlPanel%UpperRamsStatus= IDPipeRam1 BopControlPanel%LowerRamsStatus= IDPipeRam2 BopControlPanel%AnnularStatus = IDAnnular BopControlPanel%AccumulatorPressureGauge = p_acc RAM%time=0 ! WRITE(60,10) ' Overal Time','Q Ram Line','Vdis Ram Line','P Accumulator','Preg Ram Line','Preg Annular',' P BOP','ID Shear Ram', & ! 'ID Pipe Ram1','ID Pipe Ram2','ID Annular' !10 FORMAT(11(A18)) ! ! ! ! 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)) BopControlPanel%MiddleRamsOpenLED = LedOn MiddleRamsOpenLEDMine = LedOn BopControlPanel%MiddleRamsCloseLED = LedOff MiddleRamsCloseLEDMine = LedOff ShearRamIsOpening = .false. ShearRamIsClosing = .false. BopControlPanel%UpperRamsOpenLED = LedOn UpperRamsOpenLEDMine = LedOn BopControlPanel%UpperRamsCloseLED = LedOff UpperRamsCloseLEDMine = LedOff PipeRam1IsOpening = .false. PipeRam1IsClosing = .false. BopControlPanel%LowerRamsOpenLED = LedOn LowerRamsOpenLEDMine = LedOn BopControlPanel%LowerRamsCloseLED = LedOff LowerRamsCloseLEDMine = LedOff PipeRam2IsOpening = .false. PipeRam2IsClosing = .false. BopControlPanel%ChokeLineOpenLED = LedOff ChokeLineOpenLEDMine = LedOff BopControlPanel%ChokeLineCloseLED = LedOn ChokeLineCloseLEDMine = LedOn ChokeLineIsOpening = .false. ChokeLineIsClosing = .false. BopControlPanel%KillLineOpenLED = LedOff KillLineOpenLedMine = LedOff BopControlPanel%KillLineCloseLED = LedOn KillLineCloseLedMine = LedOn KillLineIsOpening = .false. KillLineIsClosing = .false. BopControlPanel%AnnularOpenLED = LedOn AnnularOpenLedMine = LedOn BopControlPanel%AnnularCloseLED = LedOff AnnularCloseLedMine = LedOff AnnularIsOpening = .false. AnnularIsClosing = .false. FirstSet=1 RamsFirstSet=1 BopControlPanel%ManifoldPressureGauge=prams_regset !RamsReglatorSet BopControlPanel%AnnularPressureGauge= (1 - AnnularPressureGaugeMalf) * min(BopControlPanel%AnnularRegulatorSetControl,1700.) PannularTimeStepDelay = int(1./DeltaT_BOP) ! 1/0.1 : for 1 sec delay in AnnRegulator shot time DO i = 1 , PannularTimeStepDelay CALL Pannular_regDelay%AddToFirst(BopControlPanel%AnnularPressureGauge) END DO end