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.
 
 
 
 
 
 

103 lines
8.5 KiB

  1. MODULE KickVARIABLESModule
  2. use DynamicDoubleArray, only:DynamicDoubleArrayType
  3. USE DynamicIntegerArray,only: DynamicIntegerArrayType
  4. USE DynamicRealArray,only:DynamicRealArrayType
  5. IMPLICIT NONE
  6. ! TYPE :: KickVARIABLESTYPE
  7. REAL :: DrillStringSpeed ! drill string speed during surge and swab [ft/s]
  8. REAL :: ChokeDensity , OldChokeDensity ! density of fluid that exits through choke [ppg]
  9. REAL :: ChokeMinDensity ! [ppg]
  10. REAL :: MaxChokeDensityChange ! [ppg/min]
  11. INTEGER :: TotalGasKicks ! Number of gas kicks enetered well
  12. REAL :: GasKickMolarMass ! molar mass of gas kick [lbm/lbmole]
  13. REAL :: GasKickBg ! Gas formation volume factor [bbl/SCF]
  14. REAL :: GasResPressure , GasResTemperature , GasResCompressibility ! pressure [psi] , temperature [R] and compressibility [-] at reservoir condition
  15. REAL :: GasReservoirDensity ! density of gas kick in reservoir condition [ppg]
  16. REAL :: BottomHolePress , BottomHoleTemperature , BottomHoleCompressibility ! pressure [psi] , temperature [R] and compressibility [-] at bottom hole condition
  17. REAL :: KickFluxAvgTemperature , KickFluxAvgPressure , KickFluxAvgCompressibility ! Average pressure [psia] and temperature [R] for calculating gas kick flux
  18. REAL :: GasKickViscosity ! Gas kick viscosity at average condition [cp]
  19. REAL :: GasKickSIDensity ! density of gas kick in average condition and in SI units [gr/cm^3]
  20. REAL :: GasKickDensity ! [ppg]
  21. REAL :: GasKickPumpFlowRate ! change of volume of gas kick in sense of flow rate [gpm]
  22. REAL :: FormPressure , FormTemperature
  23. REAL(8) :: KickFormLength , KickFormTopMD , KickFormDownMD ! [ft]
  24. REAL :: FormPermeability ! formation permeability [mD]
  25. REAL :: GasSpecGravity ! specific gravity of gas kick relative to air [-]
  26. REAL :: KickTc , KickPc ! critical temperature [R] and pressure [psi] of gas kick
  27. REAL :: KickTr , KickPr ! Reduced temperature and pressure of gas kick at reservoir condition
  28. REAL :: K_BHTpr , K_BHPpr ! Reduced temperature and pressure of gas kick at bottom hole condition
  29. REAL :: K_A_Res , K_B_Res , K_C_Res , K_D_Res ! Coefficients in calculating compressibility at reservoir condition
  30. REAL :: K_A_Bottomhole , K_B_Bottomhole , K_C_Bottomhole , K_D_Bottomhole
  31. ! Coefficients in calculating compressibility at bottomhole condition
  32. REAL :: K_Aa , K_Bb , K_Cc ! Coefficient in calculating gas viscosity at reservoir condition
  33. REAL :: MinKickVol ! minimum of kick volume at the beginning of entrance to wellbore [gal]
  34. REAL :: MinAllowableKickVol ! minimum allowable kick volume [ft^3]
  35. REAL :: SecondaryKickVol ! Volume of kicks other than first kick in reservoir condition [bbl]
  36. REAL :: SecondaryKickWeight ! Weight of kicks other than first kick in reservoir condition [lbm]
  37. REAL :: Kickmdot ! mass flow rate of kick [lbm/sec]
  38. REAL :: ExitMass ! escaped mass from choke [lbm]
  39. REAL :: KickmdotACoef ! coefficient in calculating mdot of kick, Eqn. 5 handnote [lbm/(sec.psi)]
  40. REAL :: KickmdotBCoef ! coefficient in calculating mdot of kick, Eqn. 5 handnote [psi]
  41. LOGICAL :: KickFlux ! .TRUE. = Bottomhole pressure is lower than reservoir pressure and thus gas
  42. ! enters the bottomhole.
  43. LOGICAL :: KickInFluxConditions ! a set of conditions, when all are true, this variable will become true
  44. LOGICAL :: WellHeadOpen ! .TRUE. = wellhead is open or flow on choke line
  45. ! .FALSE. = wellhead is close and no fluid flow out
  46. LOGICAL :: WellHeadWasOpen ! well Head Condition in last time step
  47. LOGICAL :: WellToChokeManifoldWasOpen
  48. LOGICAL :: KickOffBottom ! .TRUE. = kick starts to rise up
  49. LOGICAL :: KickSinglePocket ! when 'MakeKickSinglePacket' is active, only one pocket of kick exists in the well.
  50. LOGICAL :: SolvingEquationError
  51. LOGICAL :: KickWasExitingThroughChoke
  52. LOGICAL :: ChokeIsClosing
  53. INTEGER :: NoGasPocket ! number of gas pockets (not gas kick) in wellbore which may migrate or expand
  54. INTEGER :: KickType ! = 0 for gas kicks , = 1 for oil kicks and = 2 for water kicks
  55. INTEGER :: KickGasType ! = 1 for methane , = 2 for Hydrogen sulfide
  56. INTEGER :: ChokeKroneckerDelta ! if well to choke manifold is open and well to pit is closed ChokeKroneckerDelta = 1
  57. INTEGER :: MaxGasPocket ! = 1 if 'single pocket model' is on and = 15 if 'single pocket model' is off
  58. INTEGER , DIMENSION(:,:) , ALLOCATABLE :: GasPocketFlowEl ! This matrix makes relationship between gas pockets and flow elements,
  59. ! Further information in SUBROUTINE GasPocketFlowElementTransformer
  60. INTEGER , DIMENSION(:,:) , ALLOCATABLE :: tempGasPocketFlowEl ! a temperorary matrix using for data saving during GasPocketFlowEl manipulation
  61. REAL(8) , DIMENSION(:,:) , ALLOCATABLE :: KickJacobian , OldKickJacobian ! a matrix in which jacibian elements stored
  62. REAL(8) , DIMENSION(:) , ALLOCATABLE :: KickVandPFunction
  63. REAL(8) , DIMENSION(:) , ALLOCATABLE :: KickUnknownVector ! (2*n - 1) elements are flowrate and (2*n) elements are pressure of pockets (n >= 1)
  64. REAL , DIMENSION(:) , ALLOCATABLE :: KickCorrectionVector
  65. REAL :: KickCorrectionUnderRelaxation ! under relaxation parameter for correcting gas Kick Unknown Vector (0,1)
  66. ! = 0 means no correction between two step
  67. ! = 1 for direct correcting and no under relaxation
  68. ! END TYPE KickVARIABLESTYPE
  69. ! TYPE(KickVARIABLESTYPE) :: KickVARIABLES
  70. INTEGER :: KickIteration ! the number of itertion for calculating pressure and flowrate, when kick is in the well
  71. !!!!!!!!!!!!!!!!!!!!!!! Gas Pockets Data
  72. TYPE(DynamicDoubleArrayType) :: GasPocketOldPress , GasPocketOldVol ! pressure and volume of gas pocket at the beginning of time step [psia , ft^3]
  73. TYPE(DynamicDoubleArrayType) :: GasPocketNewPress , GasPocketNewVol ! pressure and volume of gas pocket at the end of time step [psia , ft^3]
  74. TYPE(DynamicRealArrayType) :: GasPocketOldTemp , GasPocketNewTemp ! temperature at the beginning (old) and at the end of time step [R]
  75. TYPE(DynamicRealArrayType) :: GasPocketFlowInduced , GasPocketDeltaVol ! flowrate in elements above gas pocket due to mass influx and expansion [gpm]
  76. TYPE(DynamicRealArrayType) :: GasPocketModifiedVol ! in some situation in migration process, or entering kick in a new space type
  77. ! such as entering annulus from openhole, or entering ckokeline from annulus,
  78. ! volume of gas pocket changes due to calculation process, and thus volume of
  79. ! gas pocket should be modified [10^-3 ft^3]
  80. TYPE(DynamicRealArrayType) :: GasPocketWeight ! weight of pocket [lbm]
  81. TYPE(DynamicRealArrayType) :: GasPocketDensity ! density of gas pocket [ppg]
  82. TYPE(DynamicRealArrayType) :: GasPocketCompressibility ! compressibility as a measure of deviation from ideal gas behavior [-]
  83. !INTEGER , DIMENSION(:) , ALLOCATABLE :: GasPocketGasType ! = 1 for methane , = 2 for Hydrogen Sulfide
  84. END MODULE