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