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.
 
 
 
 
 
 

125 lines
7.0 KiB

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