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.
 
 
 
 
 
 

183 lines
12 KiB

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