Simulation Core
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 
 

117 regels
5.8 KiB

  1. SUBROUTINE Utube
  2. !! This subroutine calculates flow rate when pump is off, pump is disconnected from drill pipe
  3. !! and both annulus and drill pipe are exposed to atmosphere pressure and thus a U-tube situation is occurs
  4. !! Record of revisions
  5. !! Date Programmer Discription of change
  6. !! ------ ------------ -----------------------
  7. !! 1396/07/29 Sheikh Original code
  8. !! 1396/08/09 Sheikh Two-side U-tube
  9. !!
  10. USE FricPressDropVars
  11. USE MudSystemVARIABLES
  12. USE UTUBEVARS
  13. USE Fluid_Flow_Startup_Vars
  14. IMPLICIT NONE
  15. INTEGER :: i ,j, ibit , ij , ijk
  16. REAL :: AreaBeforeBit !!! Area of element before bit in U-Tube condition [in^2]
  17. QUTubeInput = 1.0
  18. QUTubeOutput = 1.0
  19. TotFricPressLoss = 0
  20. BitPressLoss = 0
  21. PressureDp = 0
  22. PressureAnn = 0
  23. !!!!!!!!!!!!!!!!!!!!!! Bit
  24. !!!!!!!!!!!! Calculating Pressure at the bottom of drill string from mud columns in drill pipes and annulus space
  25. PressureDp = SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff)
  26. PressureAnn = SUM(FlowEl(AnnulusFirstEl : AnnulusLastEl)%StaticPressDiff)
  27. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  28. !!!!!!!!!!!! U tube:: flow from string to annulus
  29. IF ((PressureDp - PressureAnn) > UTubePressTolerance) THEN
  30. DO ijk = 1 , 10
  31. FlowEl(StringFirstEl : AnnulusLastEl)%Flowrate = QUTubeInput
  32. !WRITE (*,*) 'QUTubeInput', FlowEl(AnnulusLastEl)%Flowrate
  33. DO ij = StringFirstEl , AnnulusLastEl !!!!! Updating values of flowrates
  34. CALL FricPressDrop(ij)
  35. CALL PartialDerivativeFricToFlowRate(ij)
  36. !WRITE (*,*) 'FricPressDrop, PartialDerivative', FlowEl(ij)%FricPressLoss, FlowEl(ij)%FricToQPartialDiff, FlowEl(ij)%Length
  37. END DO
  38. !!!!!!!!!!!!!! Bit pressure drop calculation
  39. IF (BitTrue) THEN
  40. i = NoHorizontalEl + NoStringEl
  41. AreaBeforeBit = FlowEl(i)%Area * Convfttoinch**2
  42. BitPressLoss = FlowEl(i)%density * Convft3toUSgal * (FlowEl(i)%vel**2 * ((AreaBeforeBit/BitTotNozzArea)**2 - 1.)) / 2. / Convlbftolbm / Convfttoinch**2
  43. END IF
  44. !!!!!!!!!!!!!!!!!!!!!!!!!!!
  45. i = NoHorizontalEl + 1
  46. j = NoHorizontalEl + NoStringEl + NoAnnulusEl
  47. !IF (ALLOCATED(FlowEl)) THEN
  48. ! WRITE (*,*) ' H, S, A, Ch, O', NoHorizontalEl , NoStringEl , NoAnnulusEl , NoWellToChokeEl , NoOpenHoleEl
  49. !END IF
  50. TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss
  51. IF (ABS((PressureDp - PressureAnn) - TotFricPressLoss) <= UTubePressTolerance .OR. QUTubeInput < 1.0) EXIT ! tolerance set to 1.0 psi
  52. IF ((PressureDp - PressureAnn) > TotFricPressLoss) THEN
  53. QUTubeInput = QUTubeInput + ((PressureDp - PressureAnn) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)
  54. ELSE IF ((PressureDp - PressureAnn) < TotFricPressLoss) THEN
  55. QUTubeInput = QUTubeInput + ((PressureDp - PressureAnn) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)
  56. END IF
  57. !WRITE (*,*) 'QUTubeInput, TotFricPressLoss', QUTubeInput, TotFricPressLoss
  58. !WRITE (*,*) '1) PressureDp, PressureAnn', PressureDp, PressureAnn, TotFricPressLoss, QUTubeInput
  59. END DO
  60. QUTubeOutput = 0.0
  61. !!!!!!!!!!!!!!!!!!!!!!!!
  62. !!!!!!!!!!!! U tube:: flow from annulus to string
  63. ELSE IF ((PressureAnn - PressureDp) > UTubePressTolerance) THEN
  64. DO ijk = 1 , 10
  65. DO ij = NoHorizontalEl + 1 , NoHorizontalEl + NoStringEl + NoAnnulusEl !!!!! Updating values of flowrates
  66. FlowEl(ij)%Flowrate = QUTubeOutput
  67. CALL FricPressDrop(ij)
  68. CALL PartialDerivativeFricToFlowRate(ij)
  69. END DO
  70. !!!!!!!!!!!!!! Bit pressure drop calculation
  71. IF (BitTrue) THEN
  72. !DO i = NumbEl , 1 , -1 !! This loop starts from the first elements of string and check the elements to reach the bit at the bottom of string
  73. ! IF (FlowEl(i)%Id==0) CYCLE
  74. i = NoHorizontalEl + NoStringEl + 1
  75. AreaBeforeBit = FlowEl(i)%Area * Convfttoinch**2
  76. BitPressLoss = FlowEl(i)%density * Convft3toUSgal * (FlowEl(i)%vel**2 * ((AreaBeforeBit/BitTotNozzArea)**2 - 1.)) / 2. / Convlbftolbm / Convfttoinch**2
  77. !IF (FlowEl(i)%Id>0) EXIT
  78. !END DO
  79. END IF
  80. !!!!!!!!!!!!!!!!!!!!!!!!!!!
  81. i = NoHorizontalEl + 1
  82. j = NoHorizontalEl + NoStringEl + NoAnnulusEl
  83. TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss
  84. IF (ABS((PressureDp - PressureAnn) - TotFricPressLoss) <= UTubePressTolerance) EXIT ! tolerance set to 1.0 psi
  85. IF ((PressureAnn - PressureDp) > TotFricPressLoss) THEN
  86. QUTubeOutput = QUTubeOutput - (((PressureAnn - PressureDp) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff))
  87. ELSE IF ((PressureAnn - PressureDp) < TotFricPressLoss) THEN
  88. QUTubeOutput = QUTubeOutput + (((PressureAnn - PressureDp) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff))
  89. END IF
  90. !WRITE (*,*) 'QUTubeOutput, TotFricPressLoss', QUTubeOutput, TotFricPressLoss
  91. WRITE (*,*) '2) PressureDp, PressureAnn', PressureDp, PressureAnn, TotFricPressLoss
  92. END DO
  93. QUTubeInput = 0.0
  94. !!!!!!!!!!!! No U-Tube
  95. ELSE
  96. QUTubeInput = 0.0
  97. QUTubeOutput = 0.0
  98. END IF
  99. END SUBROUTINE