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.

Gas_Kick_Calculator.f90 30 KiB

1 year ago
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566
  1. SUBROUTINE GasKickCalculator
  2. USE KickVariables
  3. Use TD_WellGeometry
  4. Use CReservoirVariables
  5. Use CFormationVariables
  6. USE Fluid_Flow_Startup_Vars
  7. USE PressureDisplayVARIABLES
  8. USE FricPressDropVars
  9. USE MudSystemVARIABLES
  10. USE CMudPropertiesVariables
  11. USE CError
  12. USE , INTRINSIC :: IEEE_ARITHMETIC
  13. !! Note: a subject that may be confusing is that when we use gauge pressure and when're using absolute pressure?!
  14. !! all stated pressure are gauge pressure, so I do like this.
  15. !! only when we want to use a state equation (like ideal gas equation), we should use absolute equation and so I do this.
  16. !! Thus gas pocket pressure are all absolute pressure.
  17. IMPLICIT NONE
  18. INTEGER :: i , j , k , l
  19. SolvingEquationError = .FALSE.
  20. KickVandPFunction(:) = 0.d0
  21. KickJacobian(: , :) = 0.d0
  22. !====================================================
  23. ! Gas Properties (Methane Gas)
  24. !====================================================
  25. !GasPocketNewTemp%Array(1) = 600
  26. BottomHoleTemperature = 600
  27. KickFluxAvgPressure = (BottomHolePress + FormPressure) / 2 + StandardPress
  28. KickFluxAvgTemperature = (FormTemperature + BottomHoleTemperature) / 2
  29. KickFluxAvgCompressibility = 0.98d0
  30. K_Aa = (5.8742362 * 10.**(-3) * KickFluxAvgTemperature**1.2288) / (511.1728532 + KickFluxAvgTemperature)
  31. K_Bb = 5.5565586 + (1000.01 / KickFluxAvgTemperature)
  32. K_Cc = 2.47862 - 0.12294 * K_Bb
  33. GasKickSIDensity = KickFluxAvgPressure / (KickFluxAvgCompressibility * &
  34. KickFluxAvgTemperature * GasType(KickGasType)%GasConstant) * Convpcftogpcm3
  35. GasKickViscosity = K_Aa * EXP(K_Bb * GasKickSIDensity**K_Cc)
  36. !!!!!!!!!!!!!!!!!!!!!!!!!
  37. !!!!!!!!!!!!!! Calculating compressibility for bottom hole condition
  38. !K_BHTpr = BottomHoleTemperature / KickTc
  39. !K_BHPpr = (BottomHolePress + StandardPress) / KickPc
  40. !K_A_Bottomhole = 3.53 * K_BHPpr
  41. !K_B_Bottomhole = 10.0**(0.9813 * K_BHTpr)
  42. !K_C_Bottomhole = 0.274 * (K_BHPpr**2)
  43. !K_D_Bottomhole = 10.0**(0.8157 * K_BHTpr)
  44. BottomHoleCompressibility = 0.98d0 !1. - (K_A_Bottomhole / K_B_Bottomhole) + (K_C_Bottomhole / K_D_Bottomhole)
  45. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  46. GasKickBg = 0.00504 * KickFluxAvgCompressibility * KickFluxAvgTemperature / KickFluxAvgPressure ![bbl/SCF]
  47. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  48. !WRITE (*,*) 'Gas Kick Top'
  49. !===> Kick Flow Rate Calculation
  50. IF (FormPressure > BottomHolePress) THEN
  51. KickmdotACoef = 10.0**(-8) * 1.15741d0 * 7.080 * FormPermeability * REAL(KickFormLength) * GasType(KickGasType)%StDensity / &
  52. (GasKickViscosity * GasKickBg * LOG(10000.0))
  53. !IF (WellHeadOpen .AND. NoGasPocket == 1) KickmdotACoef = (1.d0 + 2.d0) * KickmdotACoef
  54. ELSE
  55. KickmdotACoef = 0.0
  56. END IF
  57. i = StringLastEl
  58. j = OpenholeFirstEl - 1
  59. k = GasPocketFlowEl(1 , 1)
  60. KickmdotBCoef = FormPressure + StandardPress !! - Sum(static and friction pressure loss) of flow elements below gas pocket, see below
  61. IF (FormPressure > BottomHolePress) THEN
  62. !WRITE (*,*) 'k , i, j' , k , i, j
  63. IF (k >= OpenholeFirstEl) THEN ! Bottom of active kick is in openhole
  64. KickmdotBCoef = KickmdotBCoef - (SUM(FlowEl(OpenholeFirstEl : k)%StaticPressDiff)) !+ SUM(FlowEl(j + 1 : GasPocketFlowEl(1 , 1) - 1)%FricPressLoss
  65. !WRITE (*,*) '1 SUM(FlowEl(j + 1 : k)%FricPressLoss', k, SUM(FlowEl(j + 1 : k)%FricPressLoss)
  66. ELSE IF (k < OpenholeFirstEl) THEN ! bottom of 1st gas pocket (active kick) is in annulus ond/or choke line only
  67. KickmdotBCoef = KickmdotBCoef - SUM(FlowEl(OpenholeFirstEl : NumbEl)%StaticPressDiff) &
  68. - (SUM(FlowEl(AnnulusFirstEl : k)%StaticPressDiff) + SUM(FlowEl(AnnulusFirstEl : k)%FricPressLoss))
  69. !WRITE (*,*) '2 SUM(FlowEl(j + 1 : NumbEl)%FricPressLoss', k, SUM(FlowEl(j + 1 : NumbEl)%FricPressLoss)
  70. END IF
  71. !WRITE (*,*) ' KickmdotBCoef=', KickmdotBCoef
  72. END IF
  73. !WRITE (*,*) 'Kick A, B', KickmdotACoef, KickmdotBCoef
  74. DO l = 1 , NoGasPocket
  75. KickUnknownVector(2 * l - 1) = GasPocketNewVol%Array(l)
  76. KickUnknownVector(2 * l) = GasPocketNewPress%Array(l)
  77. END DO
  78. IF (WellHeadOpen) THEN
  79. !!!!!!!!!! Calculation of functions of pocket Pressure and gas Volumes
  80. !IF (GasPocketElementNo(1) > 0) WRITE (*,*) ' GasPocketElementNo(1) ' , GasPocketElementNo(1)
  81. !WRITE (*,*) ' Kick Unknown Vector' , KickUnknownVector!(1) , KickUnknownVector(2)
  82. IF (KickIteration == 1) THEN ! updating initial guess based on previous time step data
  83. DO l = 1 , NoGasPocket
  84. KickUnknownVector(2 * l - 1) = KickUnknownVector(2 * l - 1) + GasPocketDeltaVol%Array(l)
  85. END DO
  86. END IF
  87. KickVandPFunction(1) = KickUnknownVector(1) - GasPocketCompressibility%Array(1) * GasType(KickGasType)%GasConstant * & ! VandP(1) = V(1)
  88. GasPocketNewTemp%Array(1) * (GasPocketWeight%Array(1) + KickmdotACoef * MAX(((KickmdotBCoef - KickUnknownVector(2)) * dt) , 0.0)) / KickUnknownVector(2)
  89. !WRITE (*,*) 'KickVandPFunction(1)',KickVandPFunction(1)
  90. l = 2 * NoGasPocket
  91. CALL KickFunctionsCalculator(KickVandPFunction(l) , NoGasPocket , 2) ! VandP(last) = P(last)
  92. !WRITE (*,*) 'KickVandPFunction(l)', l, KickVandPFunction(l)
  93. DO l = 2 , NoGasPocket ! VandP(Odd) = V(l, l > 1)
  94. KickVandPFunction(2 * l - 1) = KickUnknownVector(2 * l - 1) - GasPocketCompressibility%Array(l) * GasType(KickGasType)%GasConstant * &
  95. GasPocketNewTemp%Array(l) * GasPocketWeight%Array(l) / KickUnknownVector(2 * l)
  96. !WRITE(*,*) 'KickVandPFunction(V)', l, KickVandPFunction(2 * l - 1)
  97. END DO
  98. DO l = NoGasPocket - 1 , 1 , -1
  99. CALL KickFunctionsCalculator(KickVandPFunction(2 * l) , l , 1) ! VandP(Even) = P(l, l < NoGasPocket)
  100. !WRITE(*,*) 'KickVandPFunction(P)', l , KickVandPFunction(2 * l)
  101. END DO
  102. !!!!!!!!!! END - Calculation of functions of pocket Pressure and gas Volumes
  103. !!!!!!!!!! Calculation of Jacobian
  104. DO k = 1 , 2 * NoGasPocket ! Main Diagonal
  105. KickJacobian(k , k) = 1.d0
  106. END DO
  107. KickJacobian(1,2) = (GasPocketCompressibility%Array(1) * GasType(KickGasType)%GasConstant * GasPocketNewTemp%Array(1) &
  108. * (GasPocketWeight%Array(1) + KickmdotACoef * KickmdotBCoef * dt) / KickUnknownVector(2)**2) ! Row 1 Finished
  109. IF (KickJacobian(1,2) == 0.d0) THEN
  110. CALL Error('KickJacobian(1,2) = 0.0')
  111. KickJacobian(1,2) = OldKickJacobian(1,2)
  112. END IF
  113. !WRITE(*,*) 'KickJacobian(1,2)', KickJacobian(1,2)
  114. l = NoGasPocket
  115. CALL KickFunctionsCalculator(KickJacobian(2 * l , 2 * l - 1) , NoGasPocket , 4) ! for last Row
  116. IF (KickJacobian(2 * l , 2 * l - 1) == 0.d0) THEN
  117. CALL Error ('KickJacobian(Last,Odd) = 0.0')
  118. KickJacobian(2 * l , 2 * l - 1) = OldKickJacobian(2 * l , 2 * l - 1)
  119. END IF
  120. DO k = NoGasPocket - 1 , 1 , -1
  121. KickJacobian(2 * l , 2 * k - 1) = KickJacobian(2 * l , 2 * l - 1)
  122. END DO ! Last Row Finished
  123. !WRITE(*,*) 'KickJacobian(2,1)', KickJacobian(2,1)
  124. DO k = 2 , NoGasPocket
  125. KickJacobian(2 * k - 1 , 2 * k) = GasPocketCompressibility%Array(k) * GasType(KickGasType)%GasConstant * GasPocketNewTemp%Array(k) &
  126. * GasPocketWeight%Array(k) / KickUnknownVector(2 * k)**2
  127. END DO ! Odd Rows (V equations) Finished
  128. DO k = 1 , NoGasPocket - 1
  129. KickJacobian(2 * k , 2 * k + 2) = -1.d0
  130. END DO ! Even Rows (P equations) effect of upper pocket
  131. DO k = 2 , 2 * (NoGasPocket - 1) , 2
  132. DO l = 1 , k - 1 , 2
  133. CALL KickFunctionsCalculator(KickJacobian(k , l) , k / 2 , 3)
  134. IF (KickJacobian(k , l) == 0.d0) THEN
  135. WRITE (*,*) 'Jacobian Array = 0.0', k , l
  136. CALL Error ('KickJacobian(k , l) = 0.0')
  137. KickJacobian(k , l) = OldKickJacobian(k , l)
  138. END IF
  139. END DO
  140. END DO
  141. IF (ANY(IEEE_IS_NaN(KickJacobian))) CALL ErrorStop ('NaN in calculating Kick Jacobian, Call your Service Provider')
  142. !!!!!!!!!! Solving linear equation in order to finding correction vector for correcting pocket pressure and gas induced flowrates
  143. KickVandPFunction = -1.d0 * KickVandPFunction
  144. !WRITE (*,*) 'Max Remainder', MAXVAL(ABS(KickVandPFunction)) , MAXLOC(ABS(KickVandPFunction))
  145. !WRITE (*,*) 'SIZE(A , dim = 1), SIZE(A , dim = 2), SIZE(b)', SIZE(KickJacobian , dim = 1), SIZE(KickJacobian , dim = 2), SIZE(KickVandPFunction)
  146. CALL SOLVE_LINEAR_EQUATIONS(KickJacobian , KickCorrectionVector , KickVandPFunction , SolvingEquationError, SIZE(KickCorrectionVector))
  147. IF (SolvingEquationError) CALL ErrorStop( ' Error in solving kick equation ' )
  148. KickUnknownVector = KickUnknownVector + KickCorrectionUnderRelaxation * KickCorrectionVector
  149. DO l = 1 , NoGasPocket
  150. GasPocketNewVol%Array(l) = KickUnknownVector(2 * l - 1)
  151. IF (IEEE_IS_NaN(GasPocketNewVol%Array(l))) CALL ErrorStop('Volume of this pocket is Not a Number:', l)
  152. IF (GasPocketNewVol%Array(l) <= 0.d0) CALL Error('Volume of this pocket is Negative or Zero:', l)
  153. GasPocketNewPress%Array(l) = KickUnknownVector(2 * l)
  154. IF (IEEE_IS_NaN(GasPocketNewPress%Array(l))) CALL ErrorStop('Pressure of this Pocket is Not a Number:', l)
  155. IF (GasPocketNewPress%Array(l) <= 0.d0) CALL ErrorStop('Pressure of this Pocket is Negative or Zero:', l)
  156. END DO
  157. !WRITE(*,*) 'GasPocketDeltaVol (gal)' , GasPocketDeltaVol(1) * 7.48
  158. !WRITE (*,*) 'GasPocketFlowInduced (gpm), GasPocketNewVol' , GasPocketFlowInduced(1), GasPocketNewVol(1)
  159. !IF (Kchoke > 0.0)
  160. !WRITE(*,*) ' New Vol (ft3), New Press (psi)', GasPocketNewVol(1), GasPocketNewPress(1)
  161. ELSE ! well haed is closed, so build up process or migration occurs
  162. !WRITE (*,*) 'GasPocketOldPress (before)' , GasPocketOldPress(1)
  163. GasPocketNewPress%Array(1) = GasPocketOldPress%Array(1) * &
  164. (REAL((GasPocketWeight%Array(1) + KickmdotACoef * KickmdotBCoef * dt) / (GasPocketWeight%Array(1) + KickmdotACoef * GasPocketOldPress%Array(1) * dt)))
  165. !WRITE (*,*) 'GasPocketNewPress (after)' , GasPocketNewPress(1), ((GasPocketWeight(1) + KickmdotACoef * KickmdotBCoef * dt) / (GasPocketWeight(1) + KickmdotACoef * GasPocketOldPress(1) * dt))
  166. !WRITE (*,*) ' Well head is closed, GasPocketNewPress =' , GasPocketNewPress(1)
  167. !WRITE (*,*) 'Old Press, Weight, A, B' , GasPocketOldPress(1), GasPocketWeight(1), KickmdotACoef, KickmdotBCoef
  168. !WRITE (*,*) 'Numerator and denumerator Gas kick' , KickmdotACoef * KickmdotBCoef * dt , KickmdotACoef * GasPocketOldPress(1) * dt
  169. !WRITE (*,*) ' Gas Kick Volume (ft^3) = ' , GasPocketNewVol(1)
  170. END IF
  171. !DO l = 1 , NoGasPocket
  172. GasPocketDeltaVol%Array(:) = GasPocketNewVol%Array(:) - GasPocketOldVol%Array(:)
  173. GasPocketFlowInduced%Array(:) = (GasPocketDeltaVol%Array(:)) / dt * 448.8 ! gpm
  174. !END DO
  175. GasKickPumpFlowRate = 0.0
  176. IF (NOT(KickOffBottom) .AND. WellHeadOpen) GasKickPumpFlowRate = GasPocketFlowInduced%Array(1)
  177. !WRITE (*,*) ' No Iteration, KickCorrectionVector =' , KickIteration , KickCorrectionVector(1) , KickCorrectionVector(2)
  178. !WRITE (*,*) ' Kick Jacobian ', REAL(KickJacobian)
  179. !WRITE (*,*) ' KickVandPFunction = ' , REAL(KickVandPFunction)
  180. !WRITE (*,*) ' Kick Unknown Vector = ' , REAL(-KickUnknownVector)
  181. !WRITE (*,*) 'Gas Kick Bottom'
  182. END SUBROUTINE
  183. SUBROUTINE KickFunctionsCalculator(ExitValue , GasPocketNo , CalcMode)
  184. USE KickVARIABLES
  185. USE FricPressDropVars
  186. USE Fluid_Flow_Startup_Vars
  187. USE CError
  188. USE , INTRINSIC :: IEEE_Arithmetic
  189. IMPLICIT NONE
  190. REAL(8) :: ExitValue
  191. INTEGER :: GasPocketNo , CalcMode
  192. INTEGER :: x
  193. INTEGER :: y
  194. INTEGER :: z , i , j
  195. x = GasPocketFlowEl(GasPocketNo , 1)
  196. IF (GasPocketNo < NoGasPocket) y = GasPocketFlowEl(GasPocketNo + 1 , 1)
  197. i = StringLastEl
  198. j = OpenholeFirstEl - 1
  199. ! Case 1: gas pocket is completely in OP and STARTX of upper gas pocket is also
  200. ! Case 2: gas pocket is completely in OP and STARTX of upper gas pocket is above Bit
  201. ! Case 3: gas pocket is AROUNDBIT and so upper gas pocket is in ANN (or Choke line)
  202. ! Case 4: gas pocket is completely in ANN and upper gas pocket is also
  203. ! CalcMode 1: KickVandPFunction between 2 pocket
  204. ! CalcMode 2: KickVandPFunction for top gas pocket
  205. ! CalcMode 3: KickJacobian between 2 Pocket
  206. ! CalcMode 4: KickJacobian for top (last) gas pocket
  207. ! CalcMode 5: Calculating pressure of bottom pocket based on upper pocket
  208. IF (CalcMode == 1) THEN ! calculating pressure difference between two pocket, include static pressure difference and frictional
  209. ! pressure difference, use in calculating 'KickVandPFunction'
  210. ExitValue = KickUnknownVector(2 * GasPocketNo) - KickUnknownVector(2 * GasPocketNo + 2)
  211. IF (x >= OpenholeFirstEl .AND. y < OpenholeFirstEl) THEN ! Case 2 , Case 3
  212. ExitValue = ExitValue - SUM(FlowEl(x : NumbEl)%StaticPressDiff) - SUM(FlowEl(x : NumbEl)%FricPressLoss) &
  213. - SUM(FlowEl(AnnulusFirstEl : y)%StaticPressDiff) - SUM(FlowEl(AnnulusFirstEl : y)%FricPressLoss)
  214. ELSE ! Case 1 , Case 4
  215. ExitValue = ExitValue - SUM(FlowEl(x : y)%StaticPressDiff) - SUM(FlowEl(x : y)%FricPressLoss)
  216. END IF
  217. ELSE IF (CalcMode == 2) THEN
  218. ExitValue = KickUnknownVector(2 * GasPocketNo) - StandardPress - Kchoke * FlowEl(OpenholeFirstEl - 1)%Flowrate**2
  219. IF (x >= OpenholeFirstEl) THEN ! Gas Pocket is in Openhole
  220. ExitValue = ExitValue - SUM(FlowEl(x : NumbEl)%StaticPressDiff) - SUM(FlowEl(x : NumbEl)%FricPressLoss) &
  221. - SUM(FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%StaticPressDiff) - SUM(FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FricPressLoss)
  222. ELSE ! Gas Pocket is in Annulus
  223. ExitValue = ExitValue - SUM(FlowEl(x : OpenholeFirstEl - 1)%StaticPressDiff) - SUM(FlowEl(x : OpenholeFirstEl - 1)%FricPressLoss)
  224. END IF
  225. ELSE IF (CalcMode == 3) THEN ! calculating derivative of pressure difference between two pocket, relative to change in flowrate
  226. ! use in calculating 'KickJacobian'
  227. IF (x >= OpenholeFirstEl .AND. y < OpenholeFirstEl) THEN ! Top kick STARTX is in Annulus
  228. DO z = x , NumbEl ! open hole elements
  229. CALL PartialDerivativeFricToFlowRate(z)
  230. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  231. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  232. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  233. CALL ErrorStop('NaN in calculating partial derivative')
  234. END IF
  235. END DO
  236. DO z = AnnulusFirstEl , y ! Annulus elements
  237. CALL PartialDerivativeFricToFlowRate(z)
  238. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  239. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  240. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  241. CALL ErrorStop('NaN in calculating partial derivative')
  242. END IF
  243. END DO
  244. ExitValue = ExitValue - (SUM(FlowEl(x : NumbEl)%FricToQPartialDiff) + SUM(FlowEl(AnnulusFirstEl : y)%FricToQPartialDiff)) * 448.8 / dt
  245. ELSE ! both pockets are one side of bit
  246. DO z = x , y
  247. CALL PartialDerivativeFricToFlowRate(z)
  248. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  249. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  250. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  251. CALL ErrorStop('NaN in calculating partial derivative')
  252. END IF
  253. END DO
  254. ExitValue = ExitValue - SUM(FlowEl(x : y)%FricToQPartialDiff) * 448.8 / dt
  255. END IF
  256. ELSE IF (CalcMode == 4) THEN ! partial derivative of frictional pressure drop relative to flowrate for top gas pocket
  257. ExitValue = - 2.d0 * Kchoke * FlowEl(OpenholeFirstEl - 1)%Flowrate * 448.8 / dt
  258. IF (x >= OpenholeFirstEl) THEN ! kick STARTX is in openhole
  259. DO z = x , NumbEl ! open hole elements
  260. CALL PartialDerivativeFricToFlowRate(z)
  261. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  262. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  263. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  264. CALL ErrorStop('NaN in calculating partial derivative')
  265. END IF
  266. END DO
  267. DO z = AnnulusFirstEl , OpenholeFirstEl - 1 ! Annulus elements
  268. CALL PartialDerivativeFricToFlowRate(z)
  269. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  270. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  271. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  272. CALL ErrorStop('NaN in calculating partial derivative')
  273. END IF
  274. END DO
  275. ExitValue = ExitValue - (SUM(FlowEl(x : NumbEl)%FricToQPartialDiff) + SUM(FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FricToQPartialDiff)) * 448.8 / dt
  276. ELSE
  277. DO z = x , OpenholeFirstEl - 1 ! Annulus elements
  278. CALL PartialDerivativeFricToFlowRate(z)
  279. IF (IEEE_IS_NaN(FlowEl(z)%FricToQPartialDiff)) THEN
  280. WRITE (*,*) ' FricToQPartialDiff , GenRe ' , x , FlowEl(z)%FricToQPartialDiff , FlowEl(z)%GenRe
  281. WRITE (*,*) ' Op start, end, density, Q, mu' , FlowEl(z)%StartX, FlowEl(z)%EndX, FlowEl(z)%Density, FlowEl(z)%FlowRate, FlowEl(z)%mueff
  282. CALL ErrorStop('NaN in calculating partial derivative')
  283. END IF
  284. END DO
  285. ExitValue = ExitValue - SUM(FlowEl(x : OpenholeFirstEl - 1)%FricToQPartialDiff) * 448.8 / dt
  286. END IF
  287. ELSE IF (CalcMode == 5) THEN
  288. IF (x >= OpenholeFirstEl .AND. y < OpenholeFirstEl) THEN ! Gas Pocket is in Openhole and upper pocket is in annulus
  289. !WRITE (*,*) 'x , y 1' , x, y
  290. ExitValue = GasPocketNewPress%Array(GasPocketNo + 1) + SUM(FlowEl(x : NumbEl)%StaticPressDiff) + SUM(FlowEl(AnnulusFirstEl : y)%StaticPressDiff)
  291. ELSE ! Both gas pockets are in Annulus or openhole
  292. !WRITE (*,*) 'x , y 2' , x, y
  293. ExitValue = GasPocketNewPress%Array(GasPocketNo + 1) + SUM(FlowEl(x : y)%StaticPressDiff)
  294. END IF
  295. END IF
  296. END SUBROUTINE
  297. SUBROUTINE NewGasKick
  298. USE KickVariables
  299. Use TD_WellGeometry
  300. Use CReservoirVariables
  301. Use CFormationVariables
  302. USE Fluid_Flow_Startup_Vars
  303. USE PressureDisplayVARIABLES
  304. USE FricPressDropVars
  305. USE MudSystemVARIABLES
  306. USE CMudPropertiesVariables
  307. USE CError
  308. USE , INTRINSIC :: IEEE_ARITHMETIC
  309. !! Note: a subject that may be confusing is that when we use gauge pressure and when using absolute pressure?!
  310. !! all stated pressure are gauge pressure, so I do like this.
  311. !! only when we want to use a state equation (like ideal gas equation), we should use absolute equation and so I do this.
  312. !! Thus gas pocket pressure are all absolute pressure.
  313. IMPLICIT NONE
  314. INTEGER :: i , j , k , l
  315. IF (NOT(ALLOCATED(GasPocketWeight%Array))) THEN ! 1st kick
  316. WRITE (*,*) ' New Influx 1'
  317. NoGasPocket = 1
  318. NewInfluxNumber = NewInfluxNumber + 1
  319. NewInfluxElementCreated = 0
  320. KickOffBottom = .FALSE.
  321. CALL GasPocketOldPress%AddToFirst((BottomHolePress + StandardPress) * 1.d0)
  322. CALL GasPocketNewPress%AddToFirst((BottomHolePress + StandardPress) * 1.d0)
  323. CALL GasPocketOldTemp%AddToFirst(600.0)
  324. CALL GasPocketNewTemp%AddToFirst(600.0)
  325. CALL GasPocketOldVol%AddToFirst(0.d0)
  326. CALL GasPocketNewVol%AddToFirst(0.d0)
  327. CALL GasPocketdeltaVol%AddToFirst(0.0)
  328. CALL GasPocketFlowInduced%AddToFirst(0.0)
  329. CALL GasPocketModifiedVol%AddToFirst(0.0)
  330. CALL GasPocketWeight%AddToFirst(0.0)
  331. CALL GasPocketDensity%AddToFirst(2.0)
  332. CALL GasPocketCompressibility%AddToFirst(0.98)
  333. ALLOCATE(KickJacobian(2 , 2) , OldKickJacobian(2 , 2) , KickVandPFunction(2) , KickUnknownVector(2) , KickCorrectionVector(2))
  334. BottomHoleTemperature = 600
  335. KickFluxAvgPressure = (BottomHolePress + FormPressure) / 2 + StandardPress
  336. KickFluxAvgTemperature = (FormTemperature + BottomHoleTemperature) / 2
  337. KickFluxAvgCompressibility = 0.98
  338. !K_Aa = (5.8742362 * 10.**(-3) * KickFluxAvgTemperature**1.2288) / (511.1728532 + KickFluxAvgTemperature)
  339. !K_Bb = 5.5565586 + (1000.01 / KickFluxAvgTemperature)
  340. !K_Cc = 2.47862 - 0.12294 * K_Bb
  341. GasKickSIDensity = KickFluxAvgPressure / (KickFluxAvgCompressibility * &
  342. KickFluxAvgTemperature * GasType(KickGasType)%GasConstant) * Convpcftogpcm3
  343. GasKickDensity = GasKickSIDensity * 8.3523
  344. !GasKickViscosity = K_Aa * EXP(K_Bb * GasKickSIDensity**K_Cc)
  345. !
  346. !K_BHTpr = BottomHoleTemperature / KickTc
  347. !K_BHPpr = (BottomHolePress + StandardPress) / KickPc
  348. !
  349. !K_A_Bottomhole = 3.53 * K_BHPpr
  350. !K_B_Bottomhole = 10.0**(0.9813 * K_BHTpr)
  351. !K_C_Bottomhole = 0.274 * (K_BHPpr**2)
  352. !K_D_Bottomhole = 10.0**(0.8157 * K_BHTpr)
  353. !
  354. !BottomHoleCompressibility = 0.98 !1. - (K_A_Bottomhole / K_B_Bottomhole) + (K_C_Bottomhole / K_D_Bottomhole)
  355. !
  356. !GasKickBg = 0.00504 * KickFluxAvgCompressibility * KickFluxAvgTemperature / KickFluxAvgPressure ![bbl/SCF]
  357. !KickmdotACoef = 10.**(-8) * 1.15741d0 * 7.08d0 * FormPermeability * REAL(KickFormLength) * GasType(KickGasType)%StDensity / &
  358. !(GasKickViscosity * GasKickBg * LOG(10000.d0))
  359. !IF (WellHeadOpen) KickmdotACoef = (1.0 + 2.0) * KickmdotACoef
  360. !KickmdotBCoef = FormPressure + StandardPress !! - Sum(static and friction pressure loss) of flow elements below gas pocket, see below
  361. !GasPocketWeight%Array(1) = GasKickDensity * 0.05 !KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  362. GasPocketWeight%Array(1) = GasKickDensity * MinKickVol !1.0:seyyed gofte !KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  363. GasPocketNewVol%Array(1) = GasPocketCompressibility%Array(1) * GasType(KickGasType)%GasConstant * &
  364. GasPocketNewTemp%Array(1) * GasPocketWeight%Array(1) / GasPocketNewPress%Array(1)
  365. GasPocketDeltaVol%Array(1) = 0.05 !GasPocketNewVol%Array(1)
  366. GasPocketFlowInduced%Array(1) = (GasPocketDeltaVol%Array(1)) / dt * 448.8 ! gpm
  367. GasKickPumpFlowRate = GasPocketFlowInduced%Array(1)
  368. WRITE (*,*) ' FormPressure , BottomHolePress' , FormPressure , BottomHolePress, GasKickDensity
  369. WRITE (*,*) ' No Press(psia) Vol(gal) Weight(lbm) Flow Induced(gpm)'
  370. DO i = 1 , NoGasPocket
  371. WRITE (*,102) i , GasPocketNewPress%Array(i), GasPocketNewVol%Array(i) * Convft3toUSgal, GasPocketWeight%Array(i), GasPocketFlowInduced%Array(i)
  372. END DO
  373. !ELSE IF (NoGasPocket < MaxGasPocket .AND. KickOffBottom .AND. (GasPocketNewVol%Array(1) > MinAllowableKickVol .OR. KickWasExitingThroughChoke)) THEN
  374. ELSE IF (NoGasPocket < MaxGasPocket .AND. KickOffBottom .AND. (GasPocketNewVol%Array(1) > MinAllowableKickVol .OR. ANY(GasPocketFlowEl(1 , :) == OpenholeFirstEl - 1))) THEN
  375. WRITE (*,*) ' New Influx', NoGasPocket + 1
  376. 102 FORMAT (I2, 4X, (F8.1), 3X, (F8.3), 2X, (F8.3), 8X, (F8.3))
  377. NoGasPocket = NoGasPocket + 1
  378. NewInfluxNumber = NewInfluxNumber + 1
  379. NewInfluxElementCreated = 0
  380. KickOffBottom = .FALSE.
  381. CALL GasPocketOldPress%AddToFirst((BottomHolePress + StandardPress) * 1.d0)
  382. CALL GasPocketNewPress%AddToFirst((BottomHolePress + StandardPress) * 1.d0)
  383. CALL GasPocketOldTemp%AddToFirst(600.0)
  384. CALL GasPocketNewTemp%AddToFirst(600.0)
  385. CALL GasPocketOldVol%AddToFirst(0.d0)
  386. CALL GasPocketNewVol%AddToFirst(0.d0)
  387. CALL GasPocketdeltaVol%AddToFirst(0.0)
  388. CALL GasPocketFlowInduced%AddToFirst(0.0)
  389. CALL GasPocketModifiedVol%AddToFirst(0.0)
  390. CALL GasPocketWeight%AddToFirst(0.0)
  391. CALL GasPocketDensity%AddToFirst(2.0)
  392. CALL GasPocketCompressibility%AddToFirst(0.98)
  393. DEALLOCATE(KickJacobian , OldKickJacobian , KickVandPFunction , KickUnknownVector , KickCorrectionVector)
  394. ALLOCATE(KickJacobian(2 * NoGasPocket , 2 * NoGasPocket) , OldKickJacobian(2 * NoGasPocket , 2 * NoGasPocket))
  395. ALLOCATE(KickUnknownVector(2 * NoGasPocket) , KickCorrectionVector(2 * NoGasPocket) , KickVandPFunction(2 * NoGasPocket))
  396. BottomHoleTemperature = 600
  397. KickFluxAvgPressure = (BottomHolePress + FormPressure) / 2 + StandardPress
  398. KickFluxAvgTemperature = (FormTemperature + BottomHoleTemperature) / 2
  399. KickFluxAvgCompressibility = 0.98
  400. !K_Aa = (5.8742362 * 10.**(-3) * KickFluxAvgTemperature**1.2288) / (511.1728532 + KickFluxAvgTemperature)
  401. !K_Bb = 5.5565586 + (1000.01 / KickFluxAvgTemperature)
  402. !K_Cc = 2.47862 - 0.12294 * K_Bb
  403. GasKickSIDensity = KickFluxAvgPressure / (KickFluxAvgCompressibility * &
  404. KickFluxAvgTemperature * GasType(KickGasType)%GasConstant) * Convpcftogpcm3
  405. GasKickDensity = GasKickSIDensity * 8.3523
  406. !GasKickViscosity = K_Aa * EXP(K_Bb * GasKickSIDensity**K_Cc)
  407. !
  408. !K_BHTpr = BottomHoleTemperature / KickTc
  409. !K_BHPpr = (BottomHolePress + StandardPress) / KickPc
  410. !
  411. !K_A_Bottomhole = 3.53 * K_BHPpr
  412. !K_B_Bottomhole = 10.0**(0.9813 * K_BHTpr)
  413. !K_C_Bottomhole = 0.274 * (K_BHPpr**2)
  414. !K_D_Bottomhole = 10.0**(0.8157 * K_BHTpr)
  415. !
  416. !BottomHoleCompressibility = 0.98 !1. - (K_A_Bottomhole / K_B_Bottomhole) + (K_C_Bottomhole / K_D_Bottomhole)
  417. !
  418. !GasKickBg = 0.00504 * KickFluxAvgCompressibility * KickFluxAvgTemperature / KickFluxAvgPressure ![bbl/SCF]
  419. !
  420. !
  421. !KickmdotACoef = 10.**(-8) * 1.15741d0 * 7.08d0 * FormPermeability * REAL(KickFormLength) * GasType(KickGasType)%StDensity / &
  422. ! (GasKickViscosity * GasKickBg * LOG(10000.d0))
  423. !IF (WellHeadOpen) KickmdotACoef = (1.0 + 2.0) * KickmdotACoef
  424. !
  425. !KickmdotBCoef = FormPressure + StandardPress !! - Sum(static and friction pressure loss) of flow elements below gas pocket, see below
  426. !GasPocketWeight%Array(1) = GasKickDensity * 0.05 !KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  427. GasPocketWeight%Array(1) = GasKickDensity * MinKickVol !1.0:seyyed gofte !KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  428. GasPocketNewVol%Array(1) = GasPocketCompressibility%Array(1) * GasType(KickGasType)%GasConstant * &
  429. GasPocketNewTemp%Array(1) * GasPocketWeight%Array(1) / GasPocketNewPress%Array(1)
  430. GasPocketDeltaVol%Array(1) = 0.05 !GasPocketNewVol%Array(1)
  431. GasPocketFlowInduced%Array(1) = (GasPocketDeltaVol%Array(1)) / dt * 448.8 ! gpm
  432. GasKickPumpFlowRate = GasPocketFlowInduced%Array(1)
  433. WRITE (*,*) ' FormPressure , BottomHolePress' , FormPressure , BottomHolePress, GasKickDensity
  434. WRITE (*,*) ' No Press(psia) Vol(gal) Weight(lbm) Flow Induced(gpm)'
  435. DO i = 1 , NoGasPocket
  436. WRITE (*,102) i , GasPocketNewPress%Array(i), GasPocketNewVol%Array(i) * Convft3toUSgal, GasPocketWeight%Array(i), GasPocketFlowInduced%Array(i)
  437. END DO
  438. ELSE ! no new kick, so mass of 1st kick should increase
  439. GasPocketWeight%Array(1) = GasPocketweight%Array(1) + KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  440. GasKickPumpFlowRate = GasPocketFlowInduced%Array(1)
  441. IF (NoGasPocket > 1 .OR. SecondaryKickWeight > 0.0) THEN
  442. SecondaryKickWeight = SecondaryKickWeight + KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1)) * dt
  443. SecondaryKickVol = SecondaryKickWeight / GasReservoirDensity / 42.0 ! 42 USGal = 1bbl
  444. END IF
  445. END IF
  446. END SUBROUTINE