subroutine Kick_Influx ! is called in subroutine CirculationCodeSelect Use GeoElements_FluidModule USE CMudPropertiesVariables USE MudSystemVARIABLES USE Pumps_VARIABLES use CDrillWatchVariables !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity USE sROP_Other_Variables USE sROP_Variables Use KickVariables implicit none !===========================================================WELL============================================================ !===========================================================WELL============================================================ !write(*,*) 'Kick Influx' !=================== Bottom Hole Kick Influx ENTRANCE(due to Kick) =================== MudSystemDotKick_Density= 2 MudSystemDotNewInflux_Density= MudSystemDotKick_Density if ( MudSystemDotNewInfluxElementCreated==0 ) then ! new kick is pumped- (it is set to zero in sheykh subroutine after a new kick influx) call MudSystemDotOp_Density%AddToFirst (MudSystemDotNewInflux_Density) call MudSystemDotOp_MudDischarged_Volume%AddToFirst (0.0d0) call MudSystemDotOp_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_OpSection(1)) call Op_Mud_Forehead_section%AddToFirst (1) call MudSystemDotOp_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_OpSection(1)) call Op_Mud_Backhead_section%AddToFirst (1) call MudSystemDotOp_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystemDotOp_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call Op_MudOrKick%AddToFirst (MudSystemDotNewInfluxNumber) ! KickNumber= NewInfluxNumber MudSystemDotNewInfluxElementCreated= 1 endif MudSystemDotOp_MudDischarged_Volume%Array(1)= MudSystemDotOp_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.0d0)*DeltaT_Mudline) !(gal) due to KickFlux !write(*,*) 'kick volume ok=' , Op_MudDischarged_Volume%Array(1) end subroutine Kick_Influx subroutine Instructor_CirculationMud_Edit ! is called in subroutine CirculationCodeSelect Use KickVariables Use MudSystemVARIABLES USE TD_DrillStemComponents Use CUnityInputs Use CUnityOutputs USE CKellyConnectionEnumVariables USE UTUBEVARS use sROP_Variables use sROP_Other_Variables use CDownHoleVariables implicit none if ( DownHole%AnnDrillMud == .true. .and. (Rate_of_Penetration>0. .and. MudSystemDotDeltaVolumeOp>0.0) ) then do MudSystemDotimud= 1, Ann_Density%Length() if ( Ann_MudOrKick%Array(MudSystemDotimud) == 0 ) then Ann_Density%Array(MudSystemDotimud)= (St_Density%Last() * MudSystemDotAnnulusFlowRate + 141.4296E-4*Rate_of_Penetration*Diameter_of_Bit**2)/(MudSystemDotAnnulusFlowRate+6.7995E-4*Rate_of_Penetration*Diameter_of_Bit**2) Ann_CuttingMud%Array(MudSystemDotimud)= 1 endif enddo endif if ( DownHole%AnnCirculateMud == .true. ) then do MudSystemDotimud= 1, Ann_Density%Length() if ( Ann_MudOrKick%Array(MudSystemDotimud) == 0 ) then Ann_Density%Array(MudSystemDotimud)= ActiveTankDensity Ann_CuttingMud%Array(MudSystemDotimud)= 0 endif enddo do MudSystemDotimud= 1, St_Density%Length() St_Density%Array(MudSystemDotimud)= ActiveTankDensity enddo endif end subroutine Instructor_CirculationMud_Edit subroutine ShoeLostSub ! is called in subroutine CirculationCodeSelect Use KickVariables Use MudSystemVARIABLES USE TD_DrillStemComponents Use CUnityInputs Use CUnityOutputs USE CKellyConnectionEnumVariables USE UTUBEVARS use sROP_Variables use sROP_Other_Variables use CDownHoleVariables use CShoeVariables USE PressureDisplayVARIABLES Use CWarningsVariables implicit none MudSystemDotShoeLost= .false. MudSystemDotKickexpansion_DueToMudLost= .false. MudSystemDotShoeMudPressure= PressureGauges(5) MudSystemDotUGBOSuccessionCounter = MudSystemDotUGBOSuccessionCounter + 1 !write(*,*) 'check point 1' if (Shoe%InactiveFracture == .FALSE. .AND. ((MudSystemDotShoeMudPressure >= MudSystemDotFormationLostPressure) .or. MudSystemDotShoeFractured )) then !write(*,*) 'check point 2 ,UGBOSuccessionCounter' , UGBOSuccessionCounter ! if ShoeFractured changed to true , then time counter is not needed more if ( MudSystemDotUGBOSuccessionCounter /= MudSystemDotUGBOSuccessionCounterOld+1 .and. MudSystemDotShoeFractured==.false. ) then MudSystemDotUGBOSuccessionCounter = 0 ! also in starup MudSystemDotUGBOSuccessionCounterOld = 0 ! also in starup return else MudSystemDotUGBOSuccessionCounterOld= MudSystemDotUGBOSuccessionCounter endif if ( MudSystemDotUGBOSuccessionCounter < 10 .and. MudSystemDotShoeFractured==.false.) then return endif !write(*,*) 'check point 3 ,UGBOSuccessionCounter' , UGBOSuccessionCounter MudSystemDotShoeFractured= .true. MudSystemDotShoeMudViscosity= MAX(MudSystemDotShoeMudViscosity, 12.d0) !write(*,*) 'ShoeMudDensity , ShoeMudViscosity' , ShoeMudDensity , ShoeMudViscosity MudSystemDotShoeLostCoef = 10.**(-8) * 1.15741d0 * 7.08d0 * 1000000.d0 * 1.d0 * MudSystemDotShoeMudDensity / & (MudSystemDotShoeMudViscosity * LOG(10000.d0)) !write(*,*) 'lost parameters 1' , ShoeMudPressure , FormationLostPressure MudSystemDotQlost = MAX( (MudSystemDotShoeLostCoef * (MudSystemDotShoeMudPressure - (MudSystemDotFormationLostPressure/2.0))) , 0.d0 ) if (MudSystemDotQlost > 0.0) then MudSystemDotShoeLost= .true. else MudSystemDotShoeLost= .false. endif !write(*,*) 'Qlost=' , Qlost, ShoeMudPressure, FormationLostPressure call Activate_UndergroundBlowout() do MudSystemDotimud= 1, Ann_Mud_Forehead_X%Length() IF ( MudSystemDotShoeLost .and. Shoe%ShoeDepth < Ann_Mud_Backhead_X%Array(MudSystemDotimud) .and. Shoe%ShoeDepth >= Ann_Mud_Forehead_X%Array(MudSystemDotimud) & .and. Ann_MudOrKick%Array(MudSystemDotimud) == 0 .and. WellHeadIsOpen == .FALSE. ) then MudSystemDotKickexpansion_DueToMudLost= .true. write(*,*) 'Kickexpansion_DueToMudLost' EXIT ENDIF enddo endif if (UndergroundBlowout == .false.) MudSystemDotShoeLost= .false. end subroutine ShoeLostSub