Simulation Core
Não pode escolher mais do que 25 tópicos Os tópicos devem começar com uma letra ou um número, podem incluir traços ('-') e podem ter até 35 caracteres.
 
 
 
 
 
 

239 linhas
8.9 KiB

  1. subroutine ROP_MainCalculation
  2. use sROP_Other_Variables
  3. use sROP_Variables
  4. use CStringConfigurationVariables
  5. use CformationVariables
  6. use CSimulationVariables
  7. use CDataDisplayConsoleVariables
  8. use CDrillingConsoleVariables
  9. use CmudPropertiesVariables
  10. use CHoistingVariables
  11. use CDrillingConsole
  12. use CPathGenerationVariables
  13. use RTable_VARIABLES, only: RTable
  14. use TD_DrillStemComponents
  15. use TD_WellGeometry
  16. use PressureDisplayVARIABLES
  17. use MudSystemVARIABLES
  18. use FricPressDropVars
  19. use CReservoirVariables
  20. use CWarningsVariables
  21. use TopDrive_VARIABLES, only: TDS
  22. use TD_GeneralData
  23. implicit none
  24. Integer :: i , zero_ROPcount
  25. !Real(8) :: Set_ROPGauge
  26. zero_ROPcount = 0
  27. No_of_Formations = FormationCount
  28. Drilling_verticalDepth = TD_WellTotalVerticalLength
  29. !===> MaximumWellDepthExceeded Warning
  30. if ( Drilling_verticalDepth>=(Formations(FormationCount)%Top+Formations(FormationCount)%Thickness) ) then
  31. Rate_of_Penetration = 0.0d0
  32. Call Set_ROP(Rate_of_Penetration)
  33. Call Activate_MaximumWellDepthExceeded()
  34. return
  35. end if
  36. !=====================================
  37. if ( FormationNumber/=0 .and. HideDrillingBrake==1 ) then ! Hide Drilling Brake Mode
  38. FormationNumber = FormationNumber
  39. else
  40. do i= 1,No_of_Formations
  41. FormationTopDepth = Formations(i)%Top
  42. if (Drilling_verticalDepth>=FormationTopDepth) then
  43. FormationNumber = i
  44. end if
  45. end do
  46. end if
  47. !!===> Hide Drilling Brake Mode
  48. !if ( FormationNumber==FormationNo .and. HideDrillingBrake==1 ) then !????????????
  49. ! FormationNumber = FormationNo-1
  50. !end if
  51. !!=============================
  52. !Bit_Class = BitDefinition%BitCode !????????????
  53. call Bit_Specification
  54. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$$** Variables Initialization: *$$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  55. Diameter_of_Bit = BitDefinition%BitSize ! unit : [in.] (Typical Range: 3.0 to 30.0)
  56. Number_of_Bit_Nozzles = BitDefinition%BitNozzleNo ! (Typical Values: 1 to 10)
  57. Diameter_of_Bit_Nozzle = BitDefinition%BitNozzleSize ! unit : [inch] *** basic input: [1/32 in.] (Typical Range: 8.0 to 32.0)
  58. Critical_Mud_Density = Formations(FormationNumber)%PorePressureGradient/.465d0*9.d0 ! ????????? delete ,unit : [ppg] or [lb/gal] (Typical Range: 0 to 10.0)
  59. FormationMud_Density = Formations(FormationNumber)%PorePressureGradient/0.052d0
  60. BottomHole_Pressure = PressureGauges(3) !5200 [psi]
  61. ECD = BottomHole_Pressure/(0.052*Drilling_verticalDepth)
  62. 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)
  63. !IF (ALLOCATED(FlowEl)) THEN
  64. ! Mud_Viscosity = FlowEl(NoHorizontalEl + NoStringEl)%mueff !13.5 [cP]
  65. Mud_Density = BitMudDensity ! [ppg]
  66. !ELSE
  67. Mud_Viscosity = 13.5 ! [cP]
  68. !Mud_Density = 9.2 ! [ppg]
  69. !END IF
  70. Mud_Flowrate = StringFlowRateFinal ! [gpm]
  71. 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)
  72. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$ End of Variable Initialization $$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  73. ! -----**-----**-----**-----**-----* Rate_of_Penetration Model Coefficients: *-----**-----**-----**-----**-----
  74. a1 = log(Formations(FormationNumber)%Drillablity)
  75. a2 = 1.2799d-04
  76. a3 = 1.7952d-04
  77. a4 = 4.0656d-05
  78. a5 = 2.9021d-01
  79. a6 = 9.4882d-02
  80. a7 = 2.1837d-01
  81. a8 = 4.4915d-01
  82. dt = 0.1d0 ![s]
  83. Tou_H = Formations(FormationNumber)%Abrasiveness*3600.d0 ! [hr]--->[s] ( Typical Range: 1<Abrasiveness<100 )
  84. ! -----**-----**-----**-----**--- End of Rate_of_Penetration Model Coefficients ---**-----**-----**-----**-----
  85. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$$** Main Calculations: *$$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  86. f1 = Formations(FormationNumber)%Drillablity ! 1<=Drillability<=100 [ft/h]
  87. f2 = exp(2.303d0*a2*(10000.d0 - Drilling_verticalDepth)) ! First Compaction Vairable
  88. f3 = exp(2.303d0*a3*(Drilling_verticalDepth**0.69d0)*(FormationMud_Density-9.d0)) ! Second Compaction Vairable
  89. if ( (2.303d0*a4*Drilling_verticalDepth*(FormationMud_Density-ECD))>=0.d0 ) then
  90. f4 = exp(2.303d0*a4*Drilling_verticalDepth*(FormationMud_Density-ECD)) ! Underbalance Drilling Variable
  91. else
  92. f4 = 1.0d0
  93. end if
  94. if (TD_WeightOnBit>0.d0) then
  95. Weight_on_Bit = TD_WeightOnBit/1000.d0 ![klb]
  96. else
  97. Weight_on_Bit = 0.d0
  98. end if
  99. if ( (Weight_on_Bit/Diameter_of_Bit)<Critical_Weight_on_Bit ) then
  100. f5 = 0.0d0
  101. else
  102. f5 = ( ((Weight_on_Bit/Diameter_of_Bit)-Critical_Weight_on_Bit)/(4.d0-Critical_Weight_on_Bit) )**a5
  103. end if
  104. if (DriveType==1 .and. RTable%Speed>0.d0) then
  105. Rotary_Speed = RTable%Speed ![rpm]
  106. else if (DriveType==0 .and. (TDS%Speed>0. .or. RTable%Speed>0.)) then
  107. Rotary_Speed = TDS%Speed+RTable%Speed ![rpm]
  108. else
  109. Rotary_Speed = 0.0d0
  110. end if
  111. f6 = (Rotary_Speed/100.d0)**a6
  112. f7 = exp(-a7*Bit_Wearing)
  113. Call JetImpactForce
  114. f8 = JetImpact_Force/1000.d0
  115. Rate_of_Penetration = (f1*f2*f3*f4*f5*f6*f7*f8) ![ft/h]
  116. Rate_of_Penetration = (DINT(Rate_of_Penetration*10.d0))/10.d0
  117. if ( (TD_WellTotalLength==PathGenerations(PathGenerationCount)%MeasuredDepth) ) then
  118. Set_ROPGauge = Rate_of_Penetration
  119. Call Set_ROP(Set_ROPGauge) ![ft/h]
  120. Old_ROPValue(4) = Rate_of_Penetration
  121. !print* , 'first rop=' , Old_ROPValue , Rate_of_Penetration ,&
  122. ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth
  123. else if ( ((TD_WellTotalLength+(Rate_of_Penetration*TD_TimeStep/3600.d0))-Old_ROPDepth)>=0.1 ) then
  124. do i= 1,4
  125. if ( Old_ROPValue(i)==0. ) then
  126. zero_ROPcount = zero_ROPcount+1
  127. end if
  128. end do
  129. Set_ROPGauge = (Rate_of_Penetration+Old_ROPValue(1)+Old_ROPValue(2)+Old_ROPValue(3)+Old_ROPValue(4))/sngl(5-zero_ROPcount)
  130. Call Set_ROP(Set_ROPGauge) ![ft/h]
  131. do i= 2,4
  132. Old_ROPValue(i-1) = Old_ROPValue(i)
  133. end do
  134. Old_ROPValue(4) = Rate_of_Penetration
  135. Old_ROPDepth = TD_WellTotalLength+(Rate_of_Penetration*TD_TimeStep/3600.d0)
  136. !print* , 'new rop=' , Old_ROPValue , Rate_of_Penetration ,&
  137. ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth
  138. else
  139. Call Set_ROP(Set_ROPGauge) ![ft/h]
  140. !print* , 'old rop=' , Old_ROPValue , Rate_of_Penetration ,&
  141. ! zero_ROPcount , Set_ROPGauge , Old_ROPDepth , TD_WellTotalLength , PathGenerations(PathGenerationCount)%MeasuredDepth
  142. end if
  143. if (Rotary_Speed > 0.d0) THEN
  144. 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) )
  145. !Bit_Torque = Bit_Torque/3. !bi dalil taghsim bar 3 shode(chon adad bozorg bude), baadan az rabete check shavad (seyyed gofte)
  146. else
  147. Bit_Torque = 0.d0
  148. end if
  149. if ( (Weight_on_Bit/Diameter_of_Bit)<(w_d_max) ) then
  150. 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))) )
  151. else
  152. Bit_Wearing = 1.0d0 !( Typical Range: 0<=Bit_Wearing<=1 )
  153. end if
  154. Bearing_Wear = Bearing_Wear+(dt/3600.d0)*(Rotary_Speed/100.d0/Br_Coef)*((Weight_on_Bit/4.d0/Diameter_of_Bit)**1.5d0)
  155. !print*, 'Rate_of_Penetration=', Rate_of_Penetration
  156. !!print*, 'FormationMud_Density=', FormationMud_Density
  157. !!print*, 'ECD=', ECD
  158. !!print*, 'Drilling_verticalDepth=', Drilling_verticalDepth
  159. !!print*, 'power=', (2.303*a4*Drilling_verticalDepth*(FormationMud_Density-ECD))
  160. !print*, 'Rotary_Speed=', Rotary_Speed
  161. !!
  162. !print*, 'f1=', f1
  163. !print*, 'f2=', f2
  164. !print*, 'f3=', f3
  165. !print*, 'f4=', f4
  166. !print*, 'f5=', f5
  167. !print*, 'f6=', f6
  168. !print*, 'f7=', f7
  169. !print*, 'f8=', f8
  170. !print*, '***********************'
  171. end subroutine