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.
 
 
 
 
 
 

178 lines
12 KiB

  1. MODULE FricPressDropVars
  2. !! Record of revisions
  3. !! Date Programmer Discription of change
  4. !! ------ ------------ -----------------------
  5. !! 1396/07/26 Sheikh Original code
  6. !!
  7. IMPLICIT NONE
  8. REAL :: TotFricPressLoss ! Total Frictional Pressure Loss [psi]
  9. REAL :: FlowrateNearShoe
  10. INTEGER :: NoHorizontalEl ! number of elements in horizontal pump to string line
  11. INTEGER :: NoStringEl ! number of elements in string
  12. INTEGER :: NoAnnulusEl ! number of elements in annulus space
  13. INTEGER :: NoWellToChokeEl ! number of elements in well head to choke manifold
  14. INTEGER :: NoOpenHoleEl ! number of elements in openhole
  15. INTEGER :: NumbEl ! number of flow elements in horizontal line, string, annulus and openhole
  16. INTEGER :: StringFirstEl ! number of first string element
  17. INTEGER :: StringLastEl ! number of last string element
  18. INTEGER :: AnnulusFirstEl ! number of first annulus element
  19. INTEGER :: AnnulusLastEl ! number of last annulus element
  20. INTEGER :: ChokeFirstEl ! number of first choke element
  21. INTEGER :: ChokeLastEl ! number of last choke element
  22. INTEGER :: OpenholeFirstEl ! number of first openhole element
  23. INTEGER :: ShoeFlowElNo ! the flow element that starts from shoe, in other word the number of upper element adjacent to shoe
  24. REAL :: KBOP ! DeltaPBOP = KBOP * Q**2 [psi * min^2 / gal^2]
  25. REAL :: KBit ! DeltaPBit = KBit * Q**2 [psi * min^2 / gal^2]
  26. !!!! Choke Variables
  27. REAL :: BackPressure , NewBackPressure ! back pressure at riser or choke line [psi]
  28. REAL :: Kchoke ! DeltaPchoke = Kchoke * Q**2 [psi * min^2 / gal^2]
  29. REAL :: TotalOpenChokeArea , OldTotalOpenChokeArea , ChokeBypassArea , NewTotalOpenChokeArea , AreaChange
  30. REAL :: BHPSafetyMargin , AChBHPTol ! BHP safety margin and BHP Tolerance in Auto Choke mode [psi]
  31. REAL(8) :: OnShakerDensity ! Outlet Density of well for displaying in drillwatch and data [ppg]
  32. LOGICAL :: FloatValveIn
  33. LOGICAL :: FloatValveOpen , FloatValveWasOpen
  34. LOGICAL :: BitTotallyPluged
  35. REAL :: ClingingFactor = 0.45 ! in calculating surge and swab pressure changes
  36. REAL :: MudCompressibility = 2.7E-6 ! Volumne change relative to Volume/1psi, for example for change of 1000 psi in pressure, volume changes 0.27% [1/psi]
  37. REAL :: FloatValveMinOpenPressure = 1.0 ! minimum pressure that opens the float valve [psi]
  38. REAL :: StMudVol ! Total mud volume of Horizontal and String that may be compressed [gal]
  39. REAL :: AnnMudVol ! Total mud volume of Bottom hole, Annulus and Choke line that may be compressed [gal]
  40. REAL :: PumpToManifoldMudVol
  41. REAL :: StCompressedMudVol ! Compressed mud volume in Horizontal and String [gal]
  42. REAL :: AnnCompressedMudVol ! Compressed mud volume in Bottom hole, Annulus and Choke line [gal]
  43. REAL :: PumpToManifoldCompressedMudVol
  44. REAL :: StDeltaPDueToCompressibility ! Pressure increase due to mud compressibility in Horizontal and String [psi]
  45. REAL :: AnnDeltaPDueToCompressibility ! Pressure increase due to mud compressibility in Bottom hole, Annulus and Choke line [psi] (usually when wellhead is closed)
  46. REAL :: PumpToManifoldDeltaPDueToCompressibility
  47. REAL :: StDeltaPtoDeltaVCompressibility ! string pressure change due to compressibility [psi/gal]
  48. REAL :: AnnDeltaPtoDeltaVCompressibility ! annulus and openhole pressure change due to compressibility [psi/gal]
  49. !!!! Problem Variables (Choke and Bit)
  50. INTEGER :: ManChoke1Plug , ManChoke2Plug ! = 1 if choke is plugged , = 0 else
  51. INTEGER :: ManChoke1Washout , ManChoke2Washout ! = 1 if choke is washed out , = 0 else
  52. INTEGER :: BitJetsPlugged , BitJetsWashedOut
  53. INTEGER :: CasingPressure_DataDisplayMalF, CasingPressure_ChokeMalF
  54. !!!!!! Note that bit is not an element in these calculations
  55. TYPE, PUBLIC :: PressDropCalcElemInfo
  56. !! Geometrical variables
  57. REAL(8) :: Length ! Length of a Flow element [ft]
  58. REAL(8) :: DepthDiff ! Difference between depth of start and end of element [ft]
  59. REAL(8) :: StartX , EndX ! start and end point (measured depth) of flow element [ft]
  60. REAL(8) :: StartTVD , EndTVD ! Start and End point True Vertical Depth of flow element [ft]
  61. REAL :: Od , Id , Dhyd ! Outer, Inner and hydraulic diameter of flow element [in]
  62. REAL :: Area ! area of element [ft^2]
  63. INTEGER :: alpha ! geometry factor: 0 = pipe (ID=0) , 1 = annulus
  64. INTEGER :: FrictionDirection ! = 1 if flowrate is positive, so frictional pressure gradient is in direction of preassumed
  65. ! flowrate, = -1 if not above condition usually in Swab conditions
  66. !! Flow variables
  67. INTEGER :: MaterialType ! = 0 for mud , = 2 for gas
  68. REAL :: volume , vel , density , FlowRate ! volume [ft^3], velocity [ft/s], density of fluid flow [ppg], flow rate [gpm]
  69. REAL :: Gf ! geometry shear rate correction [-]
  70. !! Rheological and frictional variables
  71. REAL :: Theta600 , Theta300 ! Fann data at 600 and 300 rpm as rheological data
  72. ! REAL(8) :: VelCritBing , VelCritPow ! critical velocity in Bingham Plastic and Power law model [ft/min]
  73. REAL :: muPlastic , YieldP ! plastic viscosity [cp] and yield point [lbf/(100*ft^2)]
  74. REAL :: mueff ! Effective or apparent viscosity which is used in calculation of generalized Reynolds number
  75. REAL :: nIndex , kIndex ! n: flow behaivior index [-] and k: consistency factor [lbf*s^n/(100*ft^2)]
  76. REAL :: gammaW , tauW ! shear rate at the wall [1/s] and wall shear stress [lbf/(100*ft^2)]
  77. REAL :: GenRe ! generalized Reynolds number in power law model [-]
  78. REAL :: ReCrit = 2100.0 ! Critical Reynolds number for Newtonian model and Bingham plastic model
  79. REAL :: ReCritLam , ReCritTurb ! laminar and turbulent critical Reynolds
  80. REAL :: f ! Fanning friction factor [-]
  81. REAL :: a , b ! parameters for calculationg friction factor in turbulent regime for power law model [-]
  82. LOGICAL :: LaminarRegime ! = .TRUE. if flow regime is laminar and = .FALSE. if flowregime is not
  83. LOGICAL :: TurbulentRegime ! = .TRUE. if flow regime is turbulent and = .FALSE. if flowregime is not
  84. !! Pressure change variables
  85. REAL :: StartPress , EndPress ! Pressure at start and end of an element [psi]
  86. REAL :: dPdLFric ! frictional pressure drop gradient in each element [psi/ft]
  87. REAL :: dPdLGrav ! gravitional pressure gradient = 0.052 * Density [psi/ft]
  88. REAL :: FricPressLoss ! frictional pressure loss in each element [psi]
  89. REAL :: StaticPressDiff ! static pressure difference between top and bottom of a pocket [psi] always positive
  90. REAL :: FricToQPartialDiff ! partial differentiation of friction relative to volume flow rate
  91. END TYPE PressDropCalcElemInfo
  92. TYPE (PressDropCalcElemInfo) , ALLOCATABLE :: FlowEl(:) ! FlowEl: Pressure Drop Calculation Elements The dimension is equal to the number of flow elements
  93. TYPE, PUBLIC :: FinalPressDropCalcElemInfo
  94. !!! for use in calculationg properties of a point in 'downhole view' page
  95. REAL(8) :: StartX , EndX , StartTVD , EndTVD , Length , DepthDiff ! start and end point of flow element [ft]
  96. REAL :: density ! density of fluid flow [ppg], flow rate [gpm]
  97. REAL :: StartPress ! Pressure at start of an element [psi]
  98. REAL :: EndPress ! Pressure at end of an element [psi]
  99. REAL :: dPdLFric ! frictional pressure drop gradient in each element [psi/ft]
  100. REAL :: dPdLGrav ! gravitional pressure gradient = 0.052 * Density [psi/ft]
  101. END TYPE FinalPressDropCalcElemInfo
  102. TYPE (FinalPressDropCalcElemInfo) , ALLOCATABLE :: FinalFlowEl(:) ! FlowEl: Pressure Drop Calculation Elements The dimension is equal to the number of flow elements
  103. END MODULE FricPressDropVars
  104. MODULE UTUBEVARS
  105. REAL :: QUTubeInput ! flow rate from string to annulus which caused by head difference at two sides of U-tube [gpm]
  106. REAL :: QUtubeOutput ! flow rate from annulus to string which caused by head difference at two sides of U-tube [gpm]
  107. REAL :: PressureDp ! pressure at bit or end of drill string from drill string path [psi]
  108. REAL :: PressureAnn ! pressure at bit or end of drill string from annular path [psi]
  109. END MODULE
  110. SUBROUTINE DeallocateFlowTypes
  111. USE FricPressDropVars
  112. USE PressureDisplayVARIABLES
  113. USE KickVariables
  114. IMPLICIT NONE
  115. IF (ALLOCATED(FlowEl)) DEALLOCATE(FlowEl)
  116. IF (ALLOCATED(FinalFlowEl)) DEALLOCATE(FinalFlowEl)
  117. IF (ALLOCATED(GasPocketWeight%Array)) CALL GasPocketWeight%Empty()
  118. IF (ALLOCATED(GasPocketNewPress%Array)) CALL GasPocketNewPress%Empty()
  119. IF (ALLOCATED(GasPocketOldPress%Array)) CALL GasPocketOldPress%Empty()
  120. IF (ALLOCATED(GasPocketNewTemp%Array)) CALL GasPocketNewTemp%Empty()
  121. IF (ALLOCATED(GasPocketOldTemp%Array)) CALL GasPocketOldTemp%Empty()
  122. IF (ALLOCATED(GasPocketNewVol%Array)) CALL GasPocketNewVol%Empty()
  123. IF (ALLOCATED(GasPocketOldVol%Array)) CALL GasPocketOldVol%Empty()
  124. IF (ALLOCATED(GasPocketdeltaVol%Array)) CALL GasPocketdeltaVol%Empty()
  125. IF (ALLOCATED(GasPocketModifiedVol%Array)) CALL GasPocketModifiedVol%Empty()
  126. IF (ALLOCATED(GasPocketFlowInduced%Array)) CALL GasPocketFlowInduced%Empty()
  127. IF (ALLOCATED(GasPocketDensity%Array)) CALL GasPocketDensity%Empty()
  128. IF (ALLOCATED(GasPocketCompressibility%Array)) CALL GasPocketCompressibility%Empty()
  129. IF (ALLOCATED(GasPocketFlowEl)) DEALLOCATE(GasPocketFlowEl)
  130. IF (ALLOCATED(KickJacobian)) DEALLOCATE(KickJacobian)
  131. IF (ALLOCATED(OldKickJacobian)) DEALLOCATE(OldKickJacobian)
  132. IF (ALLOCATED(KickVandPFunction)) DEALLOCATE(KickVandPFunction)
  133. IF (ALLOCATED(KickUnknownVector)) DEALLOCATE(KickUnknownVector)
  134. IF (ALLOCATED(KickCorrectionVector)) DEALLOCATE(KickCorrectionVector)
  135. END SUBROUTINE