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.
 
 
 
 
 
 

124 lines
6.5 KiB

  1. SUBROUTINE FormationInformationCalculator
  2. use KickVARIABLESModule
  3. Use TD_WellGeometry
  4. Use CReservoirVariables
  5. Use CFormationVariables
  6. USE Fluid_Flow_Startup_Vars
  7. USE CLog2
  8. USE CDownHoleVariables
  9. USE MudSystemVARIABLES
  10. use ConfigurationVariables
  11. IMPLICIT NONE
  12. INTEGER :: i
  13. REAL(8) :: WellGeoTopTVD
  14. KickVARIABLES%KickGasType = 1 ! methane
  15. !====================================================
  16. ! Formation Length Calculation
  17. !====================================================
  18. WellGeoTopTVD = 0.
  19. KickVARIABLES%KickFormTopMD = 0.
  20. KickVARIABLES%KickFormDownMD = 0.
  21. !===> Top Measured Depth of Formation
  22. Do i = 1 , TD_WellGeneral%WellIntervalsCount
  23. if ( Reservoir%FormationTop >= TD_WellGeo(i)%VerticalDepth ) then
  24. KickVARIABLES%KickFormTopMD = KickVARIABLES%KickFormTopMD + TD_WellGeo(i)%IntervalLength
  25. !WRITE (*,*) ' here 11' , TD_WellGeo(i)%IntervalLength
  26. !WRITE (*,*) ' here v11' , TD_WellGeo(i)%VerticalDepth
  27. WellGeoTopTVD = TD_WellGeo(i)%VerticalDepth
  28. else if ( Reservoir%FormationTop < TD_WellGeo(i)%VerticalDepth ) then
  29. if ( TD_WellGeo(i)%HoleType == 0 ) then
  30. KickVARIABLES%KickFormTopMD = KickVARIABLES%KickFormTopMD + ((Reservoir%FormationTop - WellGeoTopTVD)&
  31. / cos(TD_WellGeo(i)%StartAngle))
  32. !WRITE (*,*) ' here 12' , (FormationTop - WellGeoTopTVD) / cos(TD_WellGeo(i)%StartAngle)
  33. else
  34. KickVARIABLES%KickFormTopMD = KickVARIABLES%KickFormTopMD + (TD_WellGeo(i)%RCurvature &
  35. * Asin((Reservoir%FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature))
  36. !WRITE (*,*) ' here 13' , TD_WellGeo(i)%RCurvature * Asin((FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature)
  37. end if
  38. exit
  39. end if
  40. End Do
  41. !!===> Down Measured Depth of Formation
  42. WellGeoTopTVD = 0.
  43. Do i = 1 , TD_WellGeneral%WellIntervalsCount
  44. if ( (Reservoir%FormationTop + Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)>=TD_WellGeo(i)%VerticalDepth ) then
  45. KickVARIABLES%KickFormDownMD = KickVARIABLES%KickFormDownMD + TD_WellGeo(i)%IntervalLength
  46. WellGeoTopTVD = TD_WellGeo(i)%VerticalDepth
  47. else if ( (Reservoir%FormationTop+Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)<TD_WellGeo(i)%VerticalDepth ) then
  48. if ( TD_WellGeo(i)%HoleType==0 ) then
  49. KickVARIABLES%KickFormDownMD = KickVARIABLES%KickFormDownMD + (((Reservoir%FormationTop+Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)-WellGeoTopTVD)&
  50. / cos(TD_WellGeo(i)%StartAngle))
  51. else
  52. KickVARIABLES%KickFormDownMD = KickVARIABLES%KickFormDownMD + (TD_WellGeo(i)%RCurvature &
  53. * Asin((Reservoir%FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature))
  54. end if
  55. exit
  56. end if
  57. End Do
  58. !!===> Determination of Formation Length for Kick Modeling
  59. if (TD_WellGeneral%WellTotalVerticalLength >= Reservoir%FormationTop .AND. TD_WellGeneral%WellTotalVerticalLength < (Reservoir%FormationTop+Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)) then
  60. KickVARIABLES%KickFormLength = TD_WellGeneral%WellTotalLength - KickVARIABLES%KickFormTopMD ![ft]
  61. else if ( TD_WellGeneral%WellTotalVerticalLength >= (Reservoir%FormationTop + Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness) ) then
  62. KickVARIABLES%KickFormLength = KickVARIABLES%KickFormDownMD - KickVARIABLES%KickFormTopMD ![ft]
  63. else
  64. KickVARIABLES%KickFormLength = 0.
  65. end if
  66. !PermeabilityExposedHeight = KickVARIABLES%KickFormLength * FormationPermeability
  67. DownHole%PermeabilityExposedHeight = MudSystem%FluidFlowCounter - MudSystem%MudSys_timeCounter
  68. !====================================================
  69. ! Reservoir Data
  70. !====================================================
  71. KickVARIABLES%FormPermeability = Reservoir%FormationPermeability ! [mD]
  72. KickVARIABLES%FormPressure = TD_WellGeneral%WellTotalVerticalLength * Configuration%Formation%Formations(Reservoir%FormationNo)%PorePressureGradient ![psia]
  73. DownHole%FormationPressure = INT(KickVARIABLES%FormPressure)
  74. !CALL Log_2('FormPressure =' , KickVARIABLES%FormPressure)
  75. !print*, 'Formations(FormationNo)%PorePressureGradient=', Formations(FormationNo)%PorePressureGradient
  76. !print * , 'FormationNo=' , FormationNo
  77. !print * , 'TD_WellGeneral%WellTotalVerticalLength=' , TD_WellGeneral%WellTotalVerticalLength
  78. KickVARIABLES%FormTemperature = 600 ! [Ra]
  79. !WRITE (*,*) ' Formation pressure ' , KickVARIABLES%FormPressure
  80. !====================================================
  81. ! Gas Properties (Methane Gas)
  82. !====================================================
  83. KickVARIABLES%GasResTemperature = KickVARIABLES%FormTemperature
  84. KickVARIABLES%GasResPressure = KickVARIABLES%FormPressure
  85. !!!! Methane , Gas type =1
  86. KickVARIABLES%GasKickMolarMass = GasType(KickVARIABLES%KickGasType)%MolarWt ! Methane Gas [gr/mol]
  87. KickVARIABLES%GasSpecGravity = KickVARIABLES%GasKickMolarMass / GasDensityRefrence
  88. KickVARIABLES%KickTc = GasType(KickVARIABLES%KickGasType)%CritTemp
  89. KickVARIABLES%KickPc = GasType(KickVARIABLES%KickGasType)%CritPress
  90. !!!!!!!! Calculating Compressibility, viscosity for influx condition (Average of reservoir and bottomhole)
  91. KickVARIABLES%KickTr = KickVARIABLES%GasResTemperature / KickVARIABLES%KickTc
  92. KickVARIABLES%KickPr = KickVARIABLES%GasResPressure / KickVARIABLES%KickPc
  93. KickVARIABLES%K_A_Res = 3.53 * KickVARIABLES%KickPr
  94. KickVARIABLES%K_B_Res = 10.0**(0.9813 * KickVARIABLES%KickTr)
  95. KickVARIABLES%K_C_Res = 0.274 * (KickVARIABLES%KickPr**2)
  96. KickVARIABLES%K_D_Res = 10.0**(0.8157 * KickVARIABLES%KickTr)
  97. KickVARIABLES%GasResCompressibility = 0.98 !1. - (K_A_Res / K_B_Res) + (K_C_Res / K_D_Res)
  98. KickVARIABLES%GasReservoirDensity = KickVARIABLES%GasResPressure / (KickVARIABLES%GasResCompressibility * &
  99. KickVARIABLES%GasResTemperature * GasType(KickVARIABLES%KickGasType)%GasConstant) / Convft3toUSgal ! [ppg]
  100. END SUBROUTINE