subroutine ROP_MainCalculation use sROP_Other_Variables use sROP_Variables use CStringConfigurationVariables use CformationVariables use CSimulationVariables use CDataDisplayConsoleVariables use CDrillingConsoleVariables use CmudPropertiesVariables use CHoistingVariables use CDrillingConsole use CPathGenerationVariables use RTable_VARIABLES, only: RTable use TD_DrillStemComponents use TD_WellGeometry use PressureDisplayVARIABLES use MudSystemVARIABLES use FricPressDropVars use CReservoirVariables use CWarningsVariables use TopDrive_VARIABLES, only: TDS use TD_GeneralData implicit none Integer :: i , zero_ROPcount !Real(8) :: Set_ROPGauge zero_ROPcount = 0 No_of_Formations = FormationCount Drilling_verticalDepth = TD_WellTotalVerticalLength !===> MaximumWellDepthExceeded Warning if ( Drilling_verticalDepth>=(Formations(FormationCount)%Top+Formations(FormationCount)%Thickness) ) then Rate_of_Penetration = 0.0d0 Call Set_ROP(Rate_of_Penetration) Call Activate_MaximumWellDepthExceeded() return end if !===================================== if ( FormationNumber/=0 .and. HideDrillingBrake==1 ) then ! Hide Drilling Brake Mode FormationNumber = FormationNumber else do i= 1,No_of_Formations FormationTopDepth = Formations(i)%Top if (Drilling_verticalDepth>=FormationTopDepth) then FormationNumber = i end if end do end if !!===> Hide Drilling Brake Mode !if ( FormationNumber==FormationNo .and. HideDrillingBrake==1 ) then !???????????? ! FormationNumber = FormationNo-1 !end if !!============================= !Bit_Class = BitDefinition%BitCode !???????????? call Bit_Specification ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$$** Variables Initialization: *$$$$$**$$$$$**$$$$$**$$$$$**$$$$$ Diameter_of_Bit = BitDefinition%BitSize ! unit : [in.] (Typical Range: 3.0 to 30.0) Number_of_Bit_Nozzles = BitDefinition%BitNozzleNo ! (Typical Values: 1 to 10) Diameter_of_Bit_Nozzle = BitDefinition%BitNozzleSize ! unit : [inch] *** basic input: [1/32 in.] (Typical Range: 8.0 to 32.0) Critical_Mud_Density = Formations(FormationNumber)%PorePressureGradient/.465d0*9.d0 ! ????????? delete ,unit : [ppg] or [lb/gal] (Typical Range: 0 to 10.0) FormationMud_Density = Formations(FormationNumber)%PorePressureGradient/0.052d0 BottomHole_Pressure = PressureGauges(3) !5200 [psi] ECD = BottomHole_Pressure/(0.052*Drilling_verticalDepth) Critical_Weight_on_Bit = (Formations(FormationNumber)%ThresholdWeight/5.d0)-(.06d0*(Formations(FormationNumber)%ThresholdWeight-10.d0)) ! unit : [klb/in] (Typical Range: 0 to 10 ----> 0.6 to 2) !IF (ALLOCATED(FlowEl)) THEN ! Mud_Viscosity = FlowEl(NoHorizontalEl + NoStringEl)%mueff !13.5 [cP] Mud_Density = BitMudDensity ! [ppg] !ELSE Mud_Viscosity = 13.5 ! [cP] !Mud_Density = 9.2 ! [ppg] !END IF Mud_Flowrate = StringFlowRateFinal ! [gpm] Reynolds_Number = Mud_Flowrate*Mud_Density/(Mud_Viscosity*Number_of_Bit_Nozzles*Diameter_of_Bit_Nozzle) ! unit : [dimensionless] (Typical Range: 0.1 to 1000.0) ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$ End of Variable Initialization $$$$$**$$$$$**$$$$$**$$$$$**$$$$$ ! -----**-----**-----**-----**-----* Rate_of_Penetration Model Coefficients: *-----**-----**-----**-----**----- a1 = log(Formations(FormationNumber)%Drillablity) a2 = 1.2799d-04 a3 = 1.7952d-04 a4 = 4.0656d-05 a5 = 2.9021d-01 a6 = 9.4882d-02 a7 = 2.1837d-01 a8 = 4.4915d-01 dt = 0.1d0 ![s] Tou_H = Formations(FormationNumber)%Abrasiveness*3600.d0 ! [hr]--->[s] ( Typical Range: 1=0.d0 ) then f4 = exp(2.303d0*a4*Drilling_verticalDepth*(FormationMud_Density-ECD)) ! Underbalance Drilling Variable else f4 = 1.0d0 end if if (TD_WeightOnBit>0.d0) then Weight_on_Bit = TD_WeightOnBit/1000.d0 ![klb] else Weight_on_Bit = 0.d0 end if if ( (Weight_on_Bit/Diameter_of_Bit)0.d0) then Rotary_Speed = RTable%Speed ![rpm] else if (DriveType==0 .and. (TDS%Speed>0. .or. RTable%Speed>0.)) then Rotary_Speed = TDS%Speed+RTable%Speed ![rpm] else Rotary_Speed = 0.0d0 end if f6 = (Rotary_Speed/100.d0)**a6 f7 = exp(-a7*Bit_Wearing) Call JetImpactForce f8 = JetImpact_Force/1000.d0 Rate_of_Penetration = (f1*f2*f3*f4*f5*f6*f7*f8) ![ft/h] Rate_of_Penetration = (DINT(Rate_of_Penetration*10.d0))/10.d0 if ( (TD_WellTotalLength==PathGenerations(PathGenerationCount)%MeasuredDepth) ) then Set_ROPGauge = Rate_of_Penetration Call Set_ROP(Set_ROPGauge) ![ft/h] Old_ROPValue(4) = Rate_of_Penetration !print* , 'first rop=' , Old_ROPValue , Rate_of_Penetration ,& ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth else if ( ((TD_WellTotalLength+(Rate_of_Penetration*TD_TimeStep/3600.d0))-Old_ROPDepth)>=0.1 ) then do i= 1,4 if ( Old_ROPValue(i)==0. ) then zero_ROPcount = zero_ROPcount+1 end if end do Set_ROPGauge = (Rate_of_Penetration+Old_ROPValue(1)+Old_ROPValue(2)+Old_ROPValue(3)+Old_ROPValue(4))/sngl(5-zero_ROPcount) Call Set_ROP(Set_ROPGauge) ![ft/h] do i= 2,4 Old_ROPValue(i-1) = Old_ROPValue(i) end do Old_ROPValue(4) = Rate_of_Penetration Old_ROPDepth = TD_WellTotalLength+(Rate_of_Penetration*TD_TimeStep/3600.d0) !print* , 'new rop=' , Old_ROPValue , Rate_of_Penetration ,& ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth else Call Set_ROP(Set_ROPGauge) ![ft/h] !print* , 'old rop=' , Old_ROPValue , Rate_of_Penetration ,& ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth end if if (Rotary_Speed > 0.d0) THEN Bit_Torque = ( 3.79d0 + 19.17d0*sqrt( Rate_of_Penetration / (Rotary_Speed*Diameter_of_Bit)) ) * Diameter_of_Bit * Weight_on_Bit * ( 1.d0 / ( 1.d0 + 0.00021d0*Drilling_verticalDepth) ) !Bit_Torque = Bit_Torque/3. !bi dalil taghsim bar 3 shode(chon adad bozorg bude), baadan az rabete check shavad (seyyed gofte) else Bit_Torque = 0.d0 end if if ( (Weight_on_Bit/Diameter_of_Bit)<(w_d_max) ) then Bit_Wearing = Bit_Wearing +( (dt*H3/Tou_H)*((Rotary_Speed/100.d0)**H1)*((w_d_max-4.d0)/(w_d_max-(Weight_on_Bit/Diameter_of_Bit)))*((1.d0+(H2/2.d0))/(1.d0+(H2*Bit_Wearing))) ) else Bit_Wearing = 1.0d0 !( Typical Range: 0<=Bit_Wearing<=1 ) end if Bearing_Wear = Bearing_Wear+(dt/3600.d0)*(Rotary_Speed/100.d0/Br_Coef)*((Weight_on_Bit/4.d0/Diameter_of_Bit)**1.5d0) !print*, 'Rate_of_Penetration=', Rate_of_Penetration !!print*, 'FormationMud_Density=', FormationMud_Density !!print*, 'ECD=', ECD !!print*, 'Drilling_verticalDepth=', Drilling_verticalDepth !!print*, 'power=', (2.303*a4*Drilling_verticalDepth*(FormationMud_Density-ECD)) !print*, 'Rotary_Speed=', Rotary_Speed !! !print*, 'f1=', f1 !print*, 'f2=', f2 !print*, 'f3=', f3 !print*, 'f4=', f4 !print*, 'f5=', f5 !print*, 'f6=', f6 !print*, 'f7=', f7 !print*, 'f8=', f8 !print*, '***********************' end subroutine