Simulation Core
Du kannst nicht mehr als 25 Themen auswählen Themen müssen entweder mit einem Buchstaben oder einer Ziffer beginnen. Sie können Bindestriche („-“) enthalten und bis zu 35 Zeichen lang sein.
 
 
 
 
 
 

187 Zeilen
6.9 KiB

  1. !module sROP_Module
  2. !
  3. !use sROP_Variables
  4. !
  5. !contains
  6. subroutine Calculate_ROP
  7. use sROP_Other_Variables
  8. use sROP_Variables
  9. use CStringConfigurationVariables
  10. use CformationVariables
  11. Use CSimulationVariables
  12. use CmudPropertiesVariables
  13. Use RTable_VARIABLES, only: RTable
  14. use TD_DrillStemComponents
  15. use TD_WellGeometry
  16. implicit none
  17. Integer :: i , ROP_SolDuration
  18. !TD_WellTotalLength = 10000. !from T&D module ?????????????????????delete this line
  19. Bit_Wearing = 0.0d0
  20. loop1: do
  21. CALL DATE_AND_TIME(values=ROP_StartTime)
  22. No_of_Formations = FormationCount !???????????????????????????????????????????
  23. Drilling_Depth = TD_WellTotalLength !????????????????????????? change to vertical depth of well
  24. do i= 1,No_of_Formations !???????????????????????????????????????
  25. FormationTopDepth = Formations(i)%Top !???????????????????????????????????????
  26. if (Drilling_Depth>=FormationTopDepth) then !???????????????????????????????????????
  27. FormationNumber = i !???????????????????????????????????????
  28. end if !???????????????????????????????????????
  29. end do !???????????????????????????????????????
  30. !do while (FormationTopDepth < Drilling_Depth)
  31. ! FormationNumber = FormationNumber + 1
  32. ! FormationTopDepth = FormationTopDepth + Formations(FormationNumber)%Thickness
  33. !end do
  34. !Bit_Class = BitDefinition%BitCode
  35. !call bit_spec
  36. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$$** Variables Initialization: *$$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  37. Diameter_of_Bit = BitDefinition%BitSize ! unit : [in.] (Typical Range: 3.0 to 30.0)
  38. Number_of_Bit_Nozzles = BitDefinition%BitNozzleNo ! (Typical Values: 1 to 10)
  39. Diameter_of_Bit_Nozzle = BitDefinition%BitNozzleSize ! unit : [1/32 in.] (Typical Range: 8.0 to 32.0)
  40. Critical_Mud_Density = Formations(FormationNumber)%PorePressureGradient/.465*9. ! unit : [ppg] or [lb/gal] (Typical Range: 0 to 10.0)
  41. Critical_Weight_on_Bit = (Formations(FormationNumber)%ThresholdWeight/5.)-(.06*(Formations(FormationNumber)%ThresholdWeight-10.)) ! unit : [klb/in] (Typical Range: 0 to 10 ----> 0.6 to 2)
  42. Mud_Viscosity = ActivePlasticViscosity !?????????????????????????????????
  43. Mud_Density = ActiveDensity !?????????????????????????????????
  44. Mud_Flowrate = 10. ![ppg]??????????????????????????????????????????????? from fluid module
  45. 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)
  46. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$ End of Variable Initialization $$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  47. ! $$$$$**$$$$$**$$$$$**$$$$$**$$$$$** Main Calculations: *$$$$$**$$$$$**$$$$$**$$$$$**$$$$$
  48. x1 = 1. ! Drillability Variable
  49. x2 = 10000. - Drilling_Depth ! First Compaction Vairable
  50. x3 = (Drilling_Depth**0.69) * (Mud_Density - 9.) ! Second Compaction Vairable
  51. x4 = Drilling_Depth * (Mud_Density - Critical_Mud_Density) ! Underbalance Drilling Variable
  52. Condition = 1.
  53. Weight_on_Bit = TD_WeightOnBit/1000. ![klb]
  54. !Weight_on_Bit = 10.
  55. if ( Weight_on_Bit > Critical_Weight_on_Bit ) then
  56. x5 = log( ( Weight_on_Bit - Critical_Weight_on_Bit ) / (4.*Diameter_of_Bit - Critical_Weight_on_Bit) )
  57. else
  58. x5 = 0.
  59. Condition = 0.
  60. end if
  61. Rotary_Speed = RTable%Speed ![rpm]
  62. !Rotary_Speed = 20.
  63. Rotary_Speed = abs(Rotary_Speed)
  64. if ( Rotary_Speed > 0. ) then
  65. x6 = log(Rotary_Speed/100.)
  66. else
  67. x6 = 0.
  68. Condition = 0.
  69. end if
  70. x7 = -Bit_Wearing
  71. x8 = Reynolds_Number
  72. ! -----**-----**-----**-----**-----** Rate_of_Penetration Model Coefficients: *-----**-----**-----**-----**-----
  73. a1 = log(Formations(FormationNumber)%Drillablity) !3.0643e+00
  74. a2 = 1.2799e-04
  75. a3 = 1.7952e-04
  76. a4 = 4.0656e-05
  77. a5 = 2.9021e-01
  78. a6 = 9.4882e-02
  79. a7 = 2.1837e-01
  80. a8 = 4.4915e-01
  81. dt = 0.1 ![s]
  82. Tou_H = Formations(FormationNumber)%Abrasiveness ! hr
  83. ! -----**-----**-----**-----**--- End of Rate_of_Penetration Model Coefficients: ---**-----**-----**-----**-----
  84. !if ( Weight_on_Bit>0. .and. Rotary_Speed>0. .and. TD_DrillStems(1)%ComponentType==0 ) then !???????????????????????????????????????
  85. Rate_of_Penetration = Condition*exp( a1*x1+a2*x2+a3*x3+a4*x4+a5*x5+a6*x6+a7*x7+a8*x8 )
  86. !end if !???????????????????????????????????????
  87. IF (Rotary_Speed > 0.) THEN
  88. Bit_Torque = ( 3.79 + 19.17*sqrt( Rate_of_Penetration / (Rotary_Speed*Diameter_of_Bit)) ) * Diameter_of_Bit * Weight_on_Bit * ( 1. / ( 1 + 0.00021*Drilling_Depth) )
  89. else
  90. Bit_Torque = 0.
  91. endif
  92. if ( (Weight_on_Bit/Diameter_of_Bit)<(w_d_max) ) then
  93. Bit_Wearing = Bit_Wearing +( (dt*H3/Tou_H)*((Rotary_Speed/100.)**H1)*((w_d_max-4.)/(w_d_max-(Weight_on_Bit/Diameter_of_Bit)))*((1.+(H2/2.))/(1.+(H2*Bit_Wearing))) )
  94. else
  95. Bit_Wearing = 0.0d0 !( Typical Range: 0<=Bit_Wearing<=1 )
  96. end if
  97. !Drilling_Depth = Drilling_Depth + (Rate_of_Penetration*dt)
  98. !print*, 'exp=' , exp( a1*x1 + a2*x2 + a3*x3 + a4*x4 + a5*x5 + a6*x6 + a7*x7 + a8*x8 )
  99. !
  100. !print*, 'Bit_Torque=' , Bit_Torque
  101. !print*, 'Weight_on_Bit=' , Weight_on_Bit
  102. !
  103. !print*, 'Critical_Weight_on_Bit=' , Critical_Weight_on_Bit
  104. !print*, 'Condition=' , Condition
  105. !print*, 'FormationNumber=' , FormationNumber
  106. !print*, 'No_of_Formations=' , No_of_Formations
  107. !print*, 'Bit_Wearing=' , Bit_Wearing
  108. if(IsStopped == .true.) then
  109. EXIT loop1
  110. end if
  111. CALL DATE_AND_TIME(values=ROP_EndTime)
  112. ROP_SolDuration=100-(ROP_EndTime(6)*60000+ROP_EndTime(7)*1000+ROP_EndTime(8)-ROP_StartTime(6)*60000-ROP_StartTime(7)*1000-ROP_StartTime(8))
  113. if(ROP_SolDuration > 0.0d0) then
  114. CALL sleepqq(ROP_SolDuration)
  115. end if
  116. end do loop1
  117. end subroutine Calculate_ROP
  118. subroutine bit_spec
  119. use sROP_Other_Variables
  120. use sROP_Variables
  121. !H1=1.9
  122. !H2=7.
  123. !H3=1.
  124. !w_d_max=7.
  125. filename = 'Bit_Database.TXT'
  126. open (UNIT=3, FILE=filename )
  127. !print*, 'w_d_max1=' , w_d_max
  128. !print*, 'name1=' , name
  129. !openif: if ( status == 0 ) then
  130. read (3,*,IOSTAT=status) ! Get next value
  131. readloop: do i=1,14
  132. read (3,*,IOSTAT=status) name, H1, H2, H3, w_d_max ! Get next value
  133. !print*, 'w_d_max=' , w_d_max
  134. !print*, 'name=' , name
  135. if ( status /= 0 ) exit ! EXIT if not valid.
  136. if ( name == bit_Class/10) exit
  137. end do readloop
  138. !endif openif
  139. end subroutine bit_spec
  140. !end module sROP_Module