|
- # 1 "/home/admin/SimulationCore2/FluidFlow/kick/Formation_Information.f90"
- SUBROUTINE FormationInformationCalculator
-
- use KickVARIABLESModule
- use SimulationVariables !@
- Use CReservoirVariables
- Use CFormationVariables
- USE Fluid_Flow_Startup_Vars
- USE CLog2
- USE CDownHoleVariables
- USE MudSystemVARIABLES
- use SimulationVariables !@@@
- use SimulationVariables
-
- IMPLICIT NONE
-
- INTEGER :: i
- REAL(8) :: WellGeoTopTVD
-
- KickGasType = 1 ! methane
-
- !====================================================
- ! Formation Length Calculation
- !====================================================
-
- WellGeoTopTVD = 0.
- KickFormTopMD = 0.
- KickFormDownMD = 0.
- !===> Top Measured Depth of Formation
- Do i = 1 , data%State%TD_WellGeneral%WellIntervalsCount
- if ( Reservoir%FormationTop >= data%State%TD_WellGeo(i)%VerticalDepth ) then
- KickFormTopMD = KickFormTopMD + data%State%TD_WellGeo(i)%IntervalLength
- !WRITE (*,*) ' here 11' , data%State%TD_WellGeo(i)%IntervalLength
- !WRITE (*,*) ' here v11' , data%State%TD_WellGeo(i)%VerticalDepth
-
- WellGeoTopTVD = data%State%TD_WellGeo(i)%VerticalDepth
- else if ( Reservoir%FormationTop < data%State%TD_WellGeo(i)%VerticalDepth ) then
- if ( data%State%TD_WellGeo(i)%HoleType == 0 ) then
- KickFormTopMD = KickFormTopMD + ((Reservoir%FormationTop - WellGeoTopTVD)&
- / cos(data%State%TD_WellGeo(i)%StartAngle))
- !WRITE (*,*) ' here 12' , (FormationTop - WellGeoTopTVD) / cos(data%State%TD_WellGeo(i)%StartAngle)
-
- else
- KickFormTopMD = KickFormTopMD + (data%State%TD_WellGeo(i)%RCurvature &
- * Asin((Reservoir%FormationTop - WellGeoTopTVD) / data%State%TD_WellGeo(i)%RCurvature))
- !WRITE (*,*) ' here 13' , data%State%TD_WellGeo(i)%RCurvature * Asin((FormationTop - WellGeoTopTVD) / data%State%TD_WellGeo(i)%RCurvature)
-
- end if
- exit
- end if
- End Do
-
- !!===> Down Measured Depth of Formation
- WellGeoTopTVD = 0.
- Do i = 1 , data%State%TD_WellGeneral%WellIntervalsCount
- if ( (Reservoir%FormationTop + data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)>=data%State%TD_WellGeo(i)%VerticalDepth ) then
- KickFormDownMD = KickFormDownMD + data%State%TD_WellGeo(i)%IntervalLength
- WellGeoTopTVD = data%State%TD_WellGeo(i)%VerticalDepth
- else if ( (Reservoir%FormationTop+data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)<data%State%TD_WellGeo(i)%VerticalDepth ) then
- if ( data%State%TD_WellGeo(i)%HoleType==0 ) then
- KickFormDownMD = KickFormDownMD + (((Reservoir%FormationTop+data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)-WellGeoTopTVD)&
- / cos(data%State%TD_WellGeo(i)%StartAngle))
- else
- KickFormDownMD = KickFormDownMD + (data%State%TD_WellGeo(i)%RCurvature &
- * Asin((Reservoir%FormationTop - WellGeoTopTVD) / data%State%TD_WellGeo(i)%RCurvature))
- end if
- exit
- end if
- End Do
-
- !!===> Determination of Formation Length for Kick Modeling
- if (data%State%TD_WellGeneral%WellTotalVerticalLength >= Reservoir%FormationTop .AND. data%State%TD_WellGeneral%WellTotalVerticalLength < (Reservoir%FormationTop+data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)) then
- KickFormLength = data%State%TD_WellGeneral%WellTotalLength - KickFormTopMD ![ft]
- else if ( data%State%TD_WellGeneral%WellTotalVerticalLength >= (Reservoir%FormationTop + data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness) ) then
- KickFormLength = KickFormDownMD - KickFormTopMD ![ft]
- else
- KickFormLength = 0.
- end if
-
- !PermeabilityExposedHeight = KickFormLength * FormationPermeability
- data%Equipments%DownHole%PermeabilityExposedHeight = data%State%MudSystem%FluidFlowCounter - data%State%MudSystem%MudSys_timeCounter
- !====================================================
- ! Reservoir Data
- !====================================================
- FormPermeability = Reservoir%FormationPermeability ! [mD]
-
- FormPressure = data%State%TD_WellGeneral%WellTotalVerticalLength * data%Configuration%Formation%Formations(Reservoir%FormationNo)%PorePressureGradient ![psia]
- data%Equipments%DownHole%FormationPressure = INT(FormPressure)
- !CALL Log_2('FormPressure =' , FormPressure)
- !if(print_log) print*, 'Formations(FormationNo)%PorePressureGradient=', Formations(FormationNo)%PorePressureGradient
- !print * , 'FormationNo=' , FormationNo
- !print * , 'data%State%TD_WellGeneral%WellTotalVerticalLength=' , data%State%TD_WellGeneral%WellTotalVerticalLength
- FormTemperature = 600 ! [Ra]
- !WRITE (*,*) ' Formation pressure ' , FormPressure
-
-
- !====================================================
- ! Gas Properties (Methane Gas)
- !====================================================
-
- GasResTemperature = FormTemperature
- GasResPressure = FormPressure
-
- !!!! Methane , Gas type =1
- GasKickMolarMass = data%State%GasType(KickGasType)%MolarWt ! Methane Gas [gr/mol]
- GasSpecGravity = GasKickMolarMass / GasDensityRefrence
-
- KickTc = data%State%GasType(KickGasType)%CritTemp
- KickPc = data%State%GasType(KickGasType)%CritPress
-
- !!!!!!!! Calculating Compressibility, viscosity for influx condition (Average of reservoir and bottomhole)
- KickTr = GasResTemperature / KickTc
- KickPr = GasResPressure / KickPc
-
- K_A_Res = 3.53 * KickPr
- K_B_Res = 10.0**(0.9813 * KickTr)
- K_C_Res = 0.274 * (KickPr**2)
- K_D_Res = 10.0**(0.8157 * KickTr)
-
- GasResCompressibility = 0.98 !1. - (K_A_Res / K_B_Res) + (K_C_Res / K_D_Res)
-
- GasReservoirDensity = GasResPressure / (GasResCompressibility * &
- GasResTemperature * data%State%GasType(KickGasType)%GasConstant) / Convft3toUSgal ! [ppg]
-
- END SUBROUTINE
-
|