|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124 |
- SUBROUTINE FormationInformationCalculator
-
- USE KickVariables
- Use TD_WellGeometry
- Use CReservoirVariables
- Use CFormationVariables
- USE Fluid_Flow_Startup_Vars
- USE CLog2
- USE CDownHoleVariables
- USE MudSystemVARIABLES
-
-
- 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 , TD_WellIntervalsCount
- if ( FormationTop >= TD_WellGeo(i)%VerticalDepth ) then
- KickFormTopMD = KickFormTopMD + TD_WellGeo(i)%IntervalLength
- !WRITE (*,*) ' here 11' , TD_WellGeo(i)%IntervalLength
- !WRITE (*,*) ' here v11' , TD_WellGeo(i)%VerticalDepth
-
- WellGeoTopTVD = TD_WellGeo(i)%VerticalDepth
- else if ( FormationTop < TD_WellGeo(i)%VerticalDepth ) then
- if ( TD_WellGeo(i)%HoleType == 0 ) then
- KickFormTopMD = KickFormTopMD + ((FormationTop - WellGeoTopTVD)&
- / cos(TD_WellGeo(i)%StartAngle))
- !WRITE (*,*) ' here 12' , (FormationTop - WellGeoTopTVD) / cos(TD_WellGeo(i)%StartAngle)
-
- else
- KickFormTopMD = KickFormTopMD + (TD_WellGeo(i)%RCurvature &
- * Asin((FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature))
- !WRITE (*,*) ' here 13' , TD_WellGeo(i)%RCurvature * Asin((FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature)
-
- end if
- exit
- end if
- End Do
-
- !!===> Down Measured Depth of Formation
- WellGeoTopTVD = 0.
- Do i = 1 , TD_WellIntervalsCount
- if ( (FormationTop + Formations(FormationNo)%Thickness)>=TD_WellGeo(i)%VerticalDepth ) then
- KickFormDownMD = KickFormDownMD + TD_WellGeo(i)%IntervalLength
- WellGeoTopTVD = TD_WellGeo(i)%VerticalDepth
- else if ( (FormationTop+Formations(FormationNo)%Thickness)<TD_WellGeo(i)%VerticalDepth ) then
- if ( TD_WellGeo(i)%HoleType==0 ) then
- KickFormDownMD = KickFormDownMD + (((FormationTop+Formations(FormationNo)%Thickness)-WellGeoTopTVD)&
- / cos(TD_WellGeo(i)%StartAngle))
- else
- KickFormDownMD = KickFormDownMD + (TD_WellGeo(i)%RCurvature &
- * Asin((FormationTop - WellGeoTopTVD) / TD_WellGeo(i)%RCurvature))
- end if
- exit
- end if
- End Do
-
- !!===> Determination of Formation Length for Kick Modeling
- if (TD_WellTotalVerticalLength >= FormationTop .AND. TD_WellTotalVerticalLength < (FormationTop+Formations(FormationNo)%Thickness)) then
- KickFormLength = TD_WellTotalLength - KickFormTopMD ![ft]
- else if ( TD_WellTotalVerticalLength >= (FormationTop + Formations(FormationNo)%Thickness) ) then
- KickFormLength = KickFormDownMD - KickFormTopMD ![ft]
- else
- KickFormLength = 0.
- end if
-
- !PermeabilityExposedHeight = KickFormLength * FormationPermeability
- PermeabilityExposedHeight = FluidFlowCounter - MudSys_timeCounter
- !====================================================
- ! Reservoir Data
- !====================================================
- FormPermeability = FormationPermeability ! [mD]
-
- FormPressure = TD_WellTotalVerticalLength * Formations(FormationNo)%PorePressureGradient ![psia]
- FormationPressure = INT(FormPressure)
- !CALL Log_2('FormPressure =' , FormPressure)
- !print*, 'Formations(FormationNo)%PorePressureGradient=', Formations(FormationNo)%PorePressureGradient
- !print * , 'FormationNo=' , FormationNo
- !print * , 'TD_WellTotalVerticalLength=' , TD_WellTotalVerticalLength
- FormTemperature = 600 ! [Ra]
- !WRITE (*,*) ' Formation pressure ' , FormPressure
-
-
- !====================================================
- ! Gas Properties (Methane Gas)
- !====================================================
-
- GasResTemperature = FormTemperature
- GasResPressure = FormPressure
-
- !!!! Methane , Gas type =1
- GasKickMolarMass = GasType(KickGasType)%MolarWt ! Methane Gas [gr/mol]
- GasSpecGravity = GasKickMolarMass / GasDensityRefrence
-
- KickTc = GasType(KickGasType)%CritTemp
- KickPc = 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 * GasType(KickGasType)%GasConstant) / Convft3toUSgal ! [ppg]
-
- END SUBROUTINE
-
|