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
    
    KickVARIABLES%KickGasType = 1             ! methane
    
!====================================================
!               Formation Length Calculation
!====================================================
    
    WellGeoTopTVD = 0.
    KickVARIABLES%KickFormTopMD = 0.
    KickVARIABLES%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
            KickVARIABLES%KickFormTopMD = KickVARIABLES%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
                KickVARIABLES%KickFormTopMD = KickVARIABLES%KickFormTopMD + ((Reservoir%FormationTop - WellGeoTopTVD)&
                                / cos(data%State%TD_WellGeo(i)%StartAngle))
            !WRITE (*,*) ' here 12' , (FormationTop - WellGeoTopTVD) / cos(data%State%TD_WellGeo(i)%StartAngle)
                
            else
                KickVARIABLES%KickFormTopMD = KickVARIABLES%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
            KickVARIABLES%KickFormDownMD = KickVARIABLES%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
                KickVARIABLES%KickFormDownMD = KickVARIABLES%KickFormDownMD + (((Reservoir%FormationTop+data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness)-WellGeoTopTVD)&
                                / cos(data%State%TD_WellGeo(i)%StartAngle)) 
            else
                KickVARIABLES%KickFormDownMD = KickVARIABLES%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
        KickVARIABLES%KickFormLength = data%State%TD_WellGeneral%WellTotalLength - KickVARIABLES%KickFormTopMD   ![ft]
    else if ( data%State%TD_WellGeneral%WellTotalVerticalLength >= (Reservoir%FormationTop + data%Configuration%Formation%Formations(Reservoir%FormationNo)%Thickness) ) then
        KickVARIABLES%KickFormLength = KickVARIABLES%KickFormDownMD - KickVARIABLES%KickFormTopMD       ![ft]
    else
        KickVARIABLES%KickFormLength = 0.
    end if
    
    !PermeabilityExposedHeight = KickVARIABLES%KickFormLength * FormationPermeability
    DownHole%PermeabilityExposedHeight = data%State%MudSystem%FluidFlowCounter - data%State%MudSystem%MudSys_timeCounter
!====================================================
!                Reservoir Data
!====================================================
    KickVARIABLES%FormPermeability = Reservoir%FormationPermeability   ! [mD]
    
    KickVARIABLES%FormPressure = data%State%TD_WellGeneral%WellTotalVerticalLength * data%Configuration%Formation%Formations(Reservoir%FormationNo)%PorePressureGradient          ![psia]
    DownHole%FormationPressure = INT(KickVARIABLES%FormPressure)
    !CALL Log_2('FormPressure =' , KickVARIABLES%FormPressure)
    !print*, 'Formations(FormationNo)%PorePressureGradient=', Formations(FormationNo)%PorePressureGradient
    !print * , 'FormationNo=' , FormationNo
    !print * , 'data%State%TD_WellGeneral%WellTotalVerticalLength=' , data%State%TD_WellGeneral%WellTotalVerticalLength
    KickVARIABLES%FormTemperature = 600 ! [Ra]
    !WRITE (*,*) ' Formation pressure ' , KickVARIABLES%FormPressure
    
    
!====================================================
!            Gas Properties (Methane Gas)
!====================================================
    
        KickVARIABLES%GasResTemperature =  KickVARIABLES%FormTemperature
        KickVARIABLES%GasResPressure    =  KickVARIABLES%FormPressure
    
        !!!! Methane , Gas type =1
        KickVARIABLES%GasKickMolarMass = data%State%GasType(KickVARIABLES%KickGasType)%MolarWt         ! Methane Gas [gr/mol]
        KickVARIABLES%GasSpecGravity  = KickVARIABLES%GasKickMolarMass / GasDensityRefrence
    
        KickVARIABLES%KickTc = data%State%GasType(KickVARIABLES%KickGasType)%CritTemp
        KickVARIABLES%KickPc = data%State%GasType(KickVARIABLES%KickGasType)%CritPress
    
        !!!!!!!! Calculating Compressibility, viscosity for influx condition (Average of reservoir and bottomhole)
        KickVARIABLES%KickTr = KickVARIABLES%GasResTemperature / KickVARIABLES%KickTc
        KickVARIABLES%KickPr = KickVARIABLES%GasResPressure / KickVARIABLES%KickPc
    
        KickVARIABLES%K_A_Res = 3.53 * KickVARIABLES%KickPr
        KickVARIABLES%K_B_Res = 10.0**(0.9813 * KickVARIABLES%KickTr)
        KickVARIABLES%K_C_Res = 0.274 * (KickVARIABLES%KickPr**2)
        KickVARIABLES%K_D_Res = 10.0**(0.8157 * KickVARIABLES%KickTr)
    
        KickVARIABLES%GasResCompressibility = 0.98 !1. - (K_A_Res / K_B_Res) + (K_C_Res / K_D_Res)
        
        KickVARIABLES%GasReservoirDensity = KickVARIABLES%GasResPressure / (KickVARIABLES%GasResCompressibility * &
                                KickVARIABLES%GasResTemperature * data%State%GasType(KickVARIABLES%KickGasType)%GasConstant) / Convft3toUSgal      ! [ppg]
            
END SUBROUTINE