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.
 
 
 
 
 
 

278 lines
17 KiB

  1. SUBROUTINE PressureAnnAndOHDistribution
  2. !! Record of revisions
  3. !! Date Programmer Discription of change
  4. !! ------ ------------ -----------------------
  5. !! 1396/07/30 Sheikh Original code
  6. !!
  7. USE FricPressDropVarsModule
  8. USE MudSystemVARIABLES
  9. use PressureDisplayVARIABLESModule
  10. USE GeoElements_FluidModule
  11. USE Fluid_Flow_Startup_Vars
  12. use KickVARIABLESModule
  13. USE CMudPropertiesVariables
  14. USE TD_WellGeometry
  15. USE CReservoirVariables
  16. use MudSystemModule
  17. USE CHOKEVARIABLES
  18. USE CChokeManifoldVariables
  19. USE VARIABLES
  20. USE CError
  21. USE , INTRINSIC :: IEEE_ARITHMETIC
  22. IMPLICIT NONE
  23. INTEGER :: i , j , k , l
  24. INTEGER :: ifric
  25. REAL :: Fraction
  26. FricPressDropVars%KBOP = 0.0
  27. IF (KickVARIABLES%WellHeadOpen .OR. KickVARIABLES%NoGasPocket == 0) THEN !! (mud circulation is normal wellhead may be open or closed) OR (kick is in the well and well head is open)
  28. !!!!! Determining flow rate in each section
  29. i = FricPressDropVars%AnnulusFirstEl
  30. j = FricPressDropVars%OpenholeFirstEl - 1
  31. !!!!!!!!!!!!!!!!!!!!!!!!! flowrates due to external sources like pump and tripping
  32. FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = (ClingingFactor * FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%Area + FlowEl(FricPressDropVars%StringFirstEl)%Area) * KickVARIABLES%DrillStringSpeed * ConvMintoSec * Convft3toUSgal ! flowrate in annulus due to tripping
  33. FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate + REAL(MudSystem%MudVolume_InjectedToBH) * ConvMintoSec / dt ! flowrate in annulus due to pump
  34. IF (MudSystem%ShoeFractured) THEN ! reduction of flowrate due to formation fracture and lost circulation
  35. IF (ShoeFlowElNo > FricPressDropVars%AnnulusLastEl) THEN ! shoe is in openhole
  36. FlowEl(ShoeFlowElNo : FricPressDropVars%NumbEl)%FlowRate = - MudSystem%Qlost
  37. FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate - MudSystem%Qlost
  38. ELSE ! shoe is in annulus
  39. FlowEl(ShoeFlowElNo : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = FlowEl(ShoeFlowElNo : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate - MudSystem%Qlost
  40. END IF
  41. END IF
  42. !!!!!!!!!!!!!!!!!!!!!!!!!
  43. !!!!!!!!!!!!!!!!!!!!!!!!! initial guess flowrates for opening BOP or choke line
  44. IF (KickVARIABLES%WellHeadWasOpen == .FALSE. .AND. KickVARIABLES%NoGasPocket > 0 .AND. KickVARIABLES%KickIteration == 1) THEN
  45. IF (KickVARIABLES%ChokeKroneckerDelta == 1) THEN ! flow on choke line
  46. IF (FricPressDropVars%TotalOpenChokeArea < 0.01 * Choke%ChokeAreaFullyOpen) THEN
  47. WRITE (*,*) 'density , TotalOpenChokeArea' , DownHole%Density, FricPressDropVars%TotalOpenChokeArea
  48. FricPressDropVars%TotalOpenChokeArea = 0.01 * Choke%ChokeAreaFullyOpen
  49. END IF
  50. FricPressDropVars%Kchoke = (KickVARIABLES%ChokeDensity / ((2.0 * 89158.0) * (0.26 * 0.61 * FricPressDropVars%TotalOpenChokeArea)**2)) * 4.0 ! *4.d0: seyyed gofte
  51. GasPocketFlowInduced%Array(:) = MIN((0.6 / KickVARIABLES%NoGasPocket * SQRT(PressureGauges(2) / FricPressDropVars%Kchoke)) , (0.05 * GasPocketNewVol%Array(:) * ConvFt3toUSgal / 60 / dt))
  52. WRITE (*,*) ' PressureGauges(2) , Kchoke' , PressureDisplayVARIABLES%PressureGauges(2) , FricPressDropVars%Kchoke
  53. WRITE (*,*) 'Initial guess after opening choke =', GasPocketFlowInduced%Array(1)
  54. WRITE (*,*) ' valve 49 ', Manifold%Valve(49)%Status
  55. WRITE (*,*) ' valve 47 ', Manifold%Valve(47)%Status
  56. WRITE (*,*) ' valve 26 ', Manifold%Valve(26)%Status
  57. WRITE (*,*) ' valve 30 ', Manifold%Valve(30)%Status
  58. WRITE (*,*) ' valve 34 ', Manifold%Valve(34)%Status
  59. WRITE (*,*) ' valve 63 ', Manifold%Valve(63)%Status
  60. WRITE (*,*) ' valve 28 ', Manifold%Valve(28)%Status
  61. WRITE (*,*) ' valve 33 ', Manifold%Valve(33)%Status
  62. WRITE (*,*) ' valve 62 ', Manifold%Valve(62)%Status
  63. WRITE (*,*) ' valve 36 ', Manifold%Valve(36)%Status
  64. WRITE (*,*) ' valve 38 ', Manifold%Valve(38)%Status
  65. ELSE ! flow through bell nipple
  66. k = FricPressDropVars%NoHorizontalEl + FricPressDropVars%NoStringEl + FricPressDropVars%NoAnnulusEl
  67. FricPressDropVars%KBOP = FlowEl(FricPressDropVars%AnnulusLastEl)%Density / ((2.0 * 89158.0) * (0.26 * 0.61 * ShearRam%MinimumOpenArea_InBOP)**2)
  68. GasPocketFlowInduced%Array(:) = MIN((0.1 / KickVARIABLES%NoGasPocket * SQRT(PressureDisplayVARIABLES%PressureGauges(6) / FricPressDropVars%KBOP)) , (0.05 * GasPocketNewVol%Array(:) * ConvFt3toUSgal / 60 / dt))
  69. WRITE (*,*) 'PressureGauges(6), KBOP', PressureDisplayVARIABLES%PressureGauges(6), FricPressDropVars%KBOP
  70. WRITE (*,*) 'Initial guess after opening BOP =', GasPocketFlowInduced%Array(1)
  71. END IF
  72. END IF
  73. !!!!!!!!!!!!!!!!!!!!!!!!!
  74. !!!!!!!!!!!!!!!!!!!!!!!!! flowrates due to expansion of gas pockets or kick influx
  75. !i = AnnulusFirstEl
  76. !j = OpenholeFirstEl - 1
  77. IF (KickVARIABLES%NoGasPocket > 0) THEN
  78. DO l = 1 , KickVARIABLES%NoGasPocket !GasPocketFlowEl
  79. k = KickVARIABLES%GasPocketFlowEl(l , 1)
  80. !WRITE (*,*) 'KickVARIABLES%GasPocketFlowEl(l , 1)', l, k, j
  81. IF (k == 0) CALL ERRORSTOP('GasPocketFlowEl(l , 1) == 0', l)
  82. IF (k >= FricPressDropVars%OpenholeFirstEl) THEN ! gas pocket is in open hole only
  83. FlowEl(k : FricPressDropVars%NumbEl)%FlowRate = FlowEl(k : FricPressDropVars%NumbEl)%FlowRate + GasPocketFlowInduced%Array(l) ! openhole elements above pocket
  84. FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = FlowEl(FricPressDropVars%AnnulusFirstEl : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate + GasPocketFlowInduced%Array(l) ! annulus and choke line elements
  85. ELSE IF (k < FricPressDropVars%OpenholeFirstEl) THEN ! gas pocket is in annulus ond/or choke line only
  86. FlowEl(k : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = FlowEl(k : FricPressDropVars%OpenholeFirstEl - 1)%FlowRate + GasPocketFlowInduced%Array(l) ! annulus or choke line elements above pocket
  87. END IF
  88. END DO
  89. END IF
  90. !!!!!!!!!!!!!!!!!!!!!!!!!
  91. !!!!! END - Determining flow rate in each section
  92. !!!!!!!!!!!!!!!!!!!!!!!!! effect of surge and swab on frictional pressure drop direction
  93. DO l = FricPressDropVars%AnnulusFirstEl , FricPressDropVars%OpenholeFirstEl - 1
  94. IF (FlowEl(l)%FlowRate < 0.0) THEN
  95. FlowEl(l)%FrictionDirection = -1
  96. IF (FlowEl(l)%FlowRate > -1.0 * PressFlowrateTolerance .AND. ALLOCATED(GasPocketWeight%Array)) FlowEl(l)%FlowRate = - PressFlowrateTolerance
  97. ELSE
  98. FlowEl(l)%FrictionDirection = 1
  99. IF (FlowEl(l)%FlowRate < PressFlowrateTolerance .AND. ALLOCATED(GasPocketWeight%Array)) FlowEl(l)%FlowRate = PressFlowrateTolerance
  100. END IF
  101. END DO
  102. !!!!!!!!!!!!!!!!!!!!!!!!!
  103. !!!!!!!!!!!!!!!!!!!!!!!!! Calculating Back Pressure, in well to pit path back pressure = 0
  104. ! in well to choke manifold path back pressure is equal to pressure before choke not casing pressure
  105. IF (KickVARIABLES%ChokeKroneckerDelta == 1) THEN
  106. IF (FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%FlowRate < 0.0) THEN
  107. WRITE (*,*) ' Negative choke flowrate'
  108. FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%FlowRate = MAX((REAL(MudSystem%MudVolume_InjectedToBH) * ConvMintoSec / dt) , 10.0)
  109. END IF
  110. MudSystem%deltaPchoke = (FricPressDropVars%Kchoke * FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%FlowRate * ABS(FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%FlowRate)) * 1.d0
  111. IF (MudSystem%deltaPchoke < 0.d0) MudSystem%deltaPchoke = 0.d0
  112. FricPressDropVars%BackPressure = REAL(MudSystem%deltaPchoke)
  113. ELSE
  114. FricPressDropVars%BackPressure = 0.0
  115. END IF
  116. IF (IEEE_IS_NaN(FricPressDropVars%BackPressure)) CALL ErrorStop('NaN in calculating back pressure' , FlowEl(j)%FlowRate)
  117. !write(*,*) 'BackPressure=' , BackPressure
  118. !!!!!!!!!!!!!!!!!!!!!!!!! when flow passes through choke manifold, solution process may be unstable
  119. IF (KickVARIABLES%ChokeKroneckerDelta == 1) THEN ! thus we should stabilize solution
  120. IF (FricPressDropVars%TotalOpenChokeArea > 0.5 * Choke%ChokeAreaFullyOpen) THEN
  121. KickVARIABLES%KickCorrectionUnderRelaxation = 0.6
  122. ELSE IF (FricPressDropVars%TotalOpenChokeArea > 0.1 * Choke%ChokeAreaFullyOpen) THEN
  123. KickVARIABLES%KickCorrectionUnderRelaxation = 0.5
  124. ELSE ! TotalOpenChokeArea < 0.1 * ChokeAreaFullyOpen
  125. KickVARIABLES%KickCorrectionUnderRelaxation = 0.4
  126. END IF
  127. ELSE
  128. KickVARIABLES%KickCorrectionUnderRelaxation = 0.6
  129. END IF
  130. !!!!!!!!!!!!!!!!!!!!!!!!!
  131. !!!!!!!!!!!!!!!!!!!!!!!!! calculating frictional pressure drop in annulus, chooke line and open hole elements
  132. DO ifric = FricPressDropVars%AnnulusFirstEl , FricPressDropVars%NumbEl
  133. CALL FricPressDrop(ifric)
  134. !WRITE (*,*) ' element No, FlowRate , Density, FricPressLoss', ifric, FlowEl(ifric)%FlowRate, FlowEl(ifric)%Density, FlowEl(ifric)%FricPressLoss
  135. IF (IEEE_IS_NaN(FlowEl(ifric)%FricPressLoss)) THEN
  136. WRITE (*,*) 'H, S, A, Ch, O', FricPressDropVars%NoHorizontalEl , FricPressDropVars%NoStringEl , FricPressDropVars%NoAnnulusEl , FricPressDropVars%NoWellToChokeEl , FricPressDropVars%NoOpenHoleEl
  137. WRITE (*,*) 'Ann/Op start, end, density, Q, mu, Type' , FlowEl(ifric)%StartX, FlowEl(ifric)%EndX, FlowEl(ifric)%Density, FlowEl(ifric)%FlowRate, FlowEl(ifric)%mueff, FlowEl(ifric)%MaterialType
  138. CALL ErrorStop('NaN in calculating pressure drop' , ifric)
  139. END IF
  140. END DO
  141. !!!!!!!!!!!!!!!!!!!!!!!!! Pressure distribution in annulus
  142. j = FricPressDropVars%OpenholeFirstEl - 1
  143. FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%EndPress = FricPressDropVars%BackPressure
  144. FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%StartPress = FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%EndPress + FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%FricPressLoss + FlowEl(FricPressDropVars%OpenholeFirstEl - 1)%StaticPressDiff
  145. DO l = FricPressDropVars%OpenholeFirstEl - 2 , FricPressDropVars%AnnulusFirstEl , -1
  146. !WRITE (*,*) '123'
  147. FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress
  148. FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%FricPressLoss + FlowEl(l)%StaticPressDiff
  149. END DO
  150. !!!!!!!!!!!!!!!!! Pressure distribution in Open Hole
  151. FlowEl(FricPressDropVars%NumbEl)%EndPress = FlowEl(FricPressDropVars%AnnulusFirstEl)%StartPress
  152. FlowEl(FricPressDropVars%NumbEl)%StartPress = FlowEl(FricPressDropVars%NumbEl)%EndPress + FlowEl(FricPressDropVars%NumbEl)%FricPressLoss + FlowEl(FricPressDropVars%NumbEl)%StaticPressDiff
  153. DO l = FricPressDropVars%NumbEl - 1 , FricPressDropVars%OpenholeFirstEl , -1
  154. !WRITE(*,*) ' ope'
  155. FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress
  156. FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%FricPressLoss + FlowEl(l)%StaticPressDiff
  157. !WRITE (*,*) ' Length, static, frictional open' , FlowEl(i)%Length, FlowEl(i)%StaticPressDiff, FlowEl(i)%FricPressLoss
  158. !END IF
  159. END DO
  160. ELSE ! wellhead is closed and kick is in the well
  161. !WRITE (*,*) ' well head is closed'
  162. k = KickVARIABLES%GasPocketFlowEl(KickVARIABLES%NoGasPocket , 1)
  163. !WRITE (*,*) 'k, Pocket Press', k, GasPocketOldPress%Array(KickVARIABLES%NoGasPocket) - StandardPress
  164. i = FricPressDropVars%AnnulusFirstEl
  165. j = FricPressDropVars%OpenholeFirstEl - 1
  166. FlowEl(k)%StartPress = GasPocketOldPress%Array(KickVARIABLES%NoGasPocket) - StandardPress
  167. FlowEl(k)%EndPress = GasPocketOldPress%Array(KickVARIABLES%NoGasPocket) - StandardPress
  168. IF (k > FricPressDropVars%OpenholeFirstEl - 1) THEN ! Top pocket StartX is in Open hole
  169. !WRITE (*,*) 'here 1'
  170. DO l = k - 1 , FricPressDropVars%OpenholeFirstEl , -1 ! below elements in openhole
  171. !WRITE (*,*) 'here 1-1'
  172. FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress
  173. FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff
  174. END DO
  175. DO l = k + 1 , FricPressDropVars%NumbEl ! Above elements in openhole
  176. !WRITE (*,*) 'here 1-2'
  177. FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress
  178. FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff
  179. END DO
  180. FlowEl(FricPressDropVars%AnnulusFirstEl)%StartPress = FlowEl(FricPressDropVars%NumbEl)%EndPress
  181. FlowEl(FricPressDropVars%AnnulusFirstEl)%EndPress = FlowEl(FricPressDropVars%AnnulusFirstEl)%StartPress - FlowEl(FricPressDropVars%AnnulusFirstEl)%StaticPressDiff
  182. DO l = FricPressDropVars%AnnulusFirstEl + 1 , FricPressDropVars%OpenholeFirstEl - 1
  183. FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress
  184. FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff
  185. END DO
  186. ELSE ! Top pocket StartX is in annulus or choke line
  187. DO l = k - 1 , FricPressDropVars%AnnulusFirstEl , -1 ! below elements in annnulus
  188. FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress
  189. FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff
  190. END DO
  191. DO l = k + 1 , FricPressDropVars%OpenholeFirstEl - 1 ! Above elements in annulus
  192. FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress
  193. FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff
  194. END DO
  195. FlowEl(FricPressDropVars%NumbEl)%EndPress = FlowEl(FricPressDropVars%AnnulusFirstEl)%StartPress
  196. FlowEl(FricPressDropVars%NumbEl)%StartPress = FlowEl(FricPressDropVars%NumbEl)%EndPress + FlowEl(FricPressDropVars%NumbEl)%StaticPressDiff
  197. DO l = FricPressDropVars%NumbEl - 1 , FricPressDropVars%OpenholeFirstEl , -1
  198. FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress
  199. FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff
  200. END DO
  201. END IF
  202. END IF
  203. !!!!!!!!!!!!!!!!!!!!!! checking pressure for preventing NaN in pressures
  204. DO l = FricPressDropVars%OpenholeFirstEl - 1 , FricPressDropVars%AnnulusFirstEl , -1 ! annulus or choke elements
  205. !WRITE (*,*) 'start, end' , FlowEl(i)%StartX, FlowEl(i)%EndX
  206. IF (IEEE_IS_NaN(FlowEl(l)%EndPress)) THEN
  207. WRITE (*,*) 'H, S, A, Ch, O', FricPressDropVars%NoHorizontalEl , FricPressDropVars%NoStringEl , FricPressDropVars%NoAnnulusEl , FricPressDropVars%NoWellToChokeEl , FricPressDropVars%NoOpenHoleEl
  208. WRITE (*,*) 'Ann/Ch start, end, density, Q, mu' , FlowEl(l)%StartX, FlowEl(l)%EndX, FlowEl(l)%Density, FlowEl(l)%FlowRate, FlowEl(l)%mueff, FlowEl(l)%MaterialType
  209. CALL ERRORSTOP('NaN in EndPress', l)
  210. END IF
  211. END DO
  212. DO l = FricPressDropVars%NumbEl , FricPressDropVars%OpenholeFirstEl - 1 , -1 ! op elements
  213. !WRITE (*,*) 'start, end' , FlowEl(i)%StartX, FlowEl(i)%EndX
  214. IF (IEEE_IS_NaN(FlowEl(l)%EndPress)) THEN
  215. WRITE (*,*) 'H, S, A, Ch, O', FricPressDropVars%NoHorizontalEl , FricPressDropVars%NoStringEl , FricPressDropVars%NoAnnulusEl , FricPressDropVars%NoWellToChokeEl , FricPressDropVars%NoOpenHoleEl
  216. WRITE (*,*) 'Op start, end, density, Q, mu' , FlowEl(l)%StartX, FlowEl(l)%EndX, FlowEl(l)%Density, FlowEl(l)%FlowRate, FlowEl(l)%mueff, FlowEl(l)%MaterialType
  217. CALL ERRORSTOP('NaN in EndPress', l)
  218. END IF
  219. END DO
  220. !!!!!!!!!!!!!!!!!!!!!!
  221. !!!!!!!!!!!!!!!!!!!!!!
  222. KickVARIABLES%BottomHolePress = FlowEl(FricPressDropVars%OpenholeFirstEl)%StartPress
  223. !!!!!!!!!!!!!!!!!!!!!!
  224. END SUBROUTINE