|
- module CDownHoleVariables
- use CDownHoleTypes
- use CStringConfigurationVariables
- use CDownHoleActions
- use CLog4
- implicit none
- public
- type :: DownHoleType
- logical :: AnnDrillMud
- logical :: AnnCirculateMud
-
- integer :: AnnalusFluidsCount = 0
- integer :: StringFluidsCount = 0
- type(CFluid), allocatable :: AnnalusFluids(:) !, target
- type(CFluid), allocatable :: StringFluids(:)
-
- integer :: StringCount = 0
- type(CStringComponent), allocatable :: String(:)
-
- type(CBopElement), allocatable :: BopElements(:)
-
- real(8) :: DrillPipePressure
- real(8) :: CasingPressure
- real(8) :: ShoePressure
- real(8) :: BottomHolePressure
- real(8) :: FormationPressure
- real :: InfluxRate
- real :: KickVolume
- real :: SecondKickVolume
- real :: PermeabilityExposedHeight
-
- real(8) :: Density
- real(8) :: Pressure
- real(8) :: Temperature
- real(8) :: Height
- real(8) :: Volume
- end type DownHoleType
- type(DownHoleType):: DownHole
- contains
-
- subroutine SetAnnalusFluids(count, array)
- implicit none
- integer, intent(in) :: count
- integer :: i, offset
- type(CFluid), intent(inout), target :: array(count)
- type(CFluid), pointer :: item
- DownHole%AnnalusFluidsCount = count
- print*, 'AnnalusFluidsCount = ', count
- if(size(DownHole%AnnalusFluids) > 0) then
- deallocate(DownHole%AnnalusFluids)
- end if
- if(count > 0) then
- offset = 0;
- item => array(1)
- if(item%StartMd > 0) then
- DownHole%AnnalusFluidsCount = DownHole%AnnalusFluidsCount + 1
- offset = 1;
- allocate(DownHole%AnnalusFluids(DownHole%AnnalusFluidsCount))
- DownHole%AnnalusFluids(1)%StartMd = 0
- DownHole%AnnalusFluids(1)%EndMd = item%StartMd
- DownHole%AnnalusFluids(1)%Density = 0
- DownHole%AnnalusFluids(1)%MudType = FLUID_NO_MUD
- endif
-
- !if(associated(AnnalusMudCountPtr)) then
- ! call AnnalusMudCountPtr(AnnalusFluidsCount)
- !end if
- if(.not.allocated(DownHole%AnnalusFluids))allocate(DownHole%AnnalusFluids(DownHole%AnnalusFluidsCount))
- !print*, '============START-AN============'
- if(item%StartMd < 0) DownHole%AnnalusFluids(1)%StartMd = 0
- do i = 1, count
- item => array(i)
- DownHole%AnnalusFluids(i + offset)%StartMd = item%StartMd
- if(i==1) DownHole%AnnalusFluids(i)%StartMd = 0
- !print*, 'AnnalusFluids(',i,')%StartMd=', AnnalusFluids(i)%StartMd
- DownHole%AnnalusFluids(i + offset)%EndMd = item%EndMd
- !print*, 'AnnalusFluids(',i,')%EndMd=', AnnalusFluids(i)%EndMd
- DownHole%AnnalusFluids(i + offset)%Density = item%Density
- !print*, 'AnnalusFluids(',i,')%Density=', AnnalusFluids(i)%Density
- DownHole%AnnalusFluids(i + offset)%MudType = item%MudType
- !print*, 'AnnalusFluids(',i,')%MudType=', AnnalusFluids(i)%MudType
- !print*, '----------------------------'
- end do
- !print*, '============END-AN============'
- !if(associated(AnnalusMudArrayPtr)) then
- ! !AnnalusFluidsPtr => AnnalusFluids
- ! call AnnalusMudArrayPtr(AnnalusFluids)
- !end if
- end if
- end subroutine SetAnnalusFluids
-
- subroutine SetStringFluids(count, array)
- implicit none
- integer, intent(in) :: count
- integer :: i, offset !, startArr
- type(CFluid), intent(inout), target :: array(count)
- type(CFluid), pointer :: item
- DownHole%StringFluidsCount = count
- print*, 'StringFluidsCount = ', count
- if(size(DownHole%StringFluids) > 0) then
- deallocate(DownHole%StringFluids)
- end if
-
- !startArr = 1
-
- if(count > 0) then
- offset = 0;
- item => array(1)
- !
- !if(item%StartMd <= 0 .and. item%EndMd <= 0) then
- ! StringFluidsCount = StringFluidsCount - 1
- ! count = count - 1
- ! offset = offset + 1
- ! startArr = startArr + 1
- !endif
- !
- !if(count <= 0) return
-
- if(item%StartMd > 0) then
- DownHole%StringFluidsCount = DownHole%StringFluidsCount + 1
- offset = offset + 1
- allocate(DownHole%StringFluids(DownHole%StringFluidsCount))
- DownHole%StringFluids(1)%StartMd = 0
- DownHole%StringFluids(1)%EndMd = item%StartMd
- DownHole%StringFluids(1)%Density = 0
- DownHole%StringFluids(1)%MudType = FLUID_NO_MUD
- endif
-
- !if(associated(StringMudCountPtr)) then
- ! call StringMudCountPtr(count)
- !end if
- if(.not.allocated(DownHole%StringFluids))allocate(DownHole%StringFluids(DownHole%StringFluidsCount))
- !print*, '============START-ST============'
- !print*, 'count=', count
- do i = 1, count
- item => array(i)
- DownHole%StringFluids(i + offset)%StartMd = item%StartMd
- if(i==1) DownHole%StringFluids(i)%StartMd = 0
- !print*, 'StringFluids(i)%StartMd=', StringFluids(i)%StartMd
- DownHole%StringFluids(i + offset)%EndMd = item%EndMd
- !print*, 'StringFluids(i)%EndMd=', StringFluids(i)%EndMd
- DownHole%StringFluids(i + offset)%Density = item%Density
- DownHole%StringFluids(i + offset)%MudType = item%MudType
- !print*, '----------------------------'
- end do
- !!if(item%StartMd < 0) StringFluids(1)%StartMd = 0
- !!print*, '============END-ST============'
- !if(associated(StringMudArrayPtr)) then
- ! call StringMudArrayPtr(StringFluids)
- !end if
- end if
- end subroutine SetStringFluids
-
- subroutine SetString(count, array)
- use CLog3
- implicit none
- integer, intent(in) :: count
- integer :: i !, j
- type(CStringComponents), intent(inout), target :: array(count)
- type(CStringComponents), pointer :: item
- DownHole%StringCount = count
- if(size(DownHole%String) > 0) then
- deallocate(DownHole%String)
- end if
- if(count > 0) then
- !if(associated(StringComponentCountPtr)) then
- ! call StringComponentCountPtr(count)
- !end if
- allocate(DownHole%String(count))
- !j = 0
- !print*, '============CMP-ST============'
- !call Log_3( '============CMP-ST============')
- !do i = count, 1, -1
- do i = 1, count
- item => array(i)
- !String(i)%Length = item%Length
- !String(i)%TopDepth = item%TopDepth
- !String(i)%DownDepth = item%DownDepth
- !String(i)%Od = item%Od
- !String(i)%Id = item%Id
- DownHole%String(i)%ComponentType= item%ComponentType
- !j = j + 1
- DownHole%String(i)%StartMd = item%TopDepth
- DownHole%String(i)%EndMd = item%DownDepth
-
- DownHole%String(i)%ComponentType=0
- !if(item%ComponentType > 4 ) then
- ! String(i)%ComponentType=0
- ! String(i)%StartMd = 0
- !endif
- if(item%ComponentType == 3) DownHole%String(i)%ComponentType=0
- if(item%ComponentType == 4) DownHole%String(i)%ComponentType=1
- if(item%ComponentType == 2) DownHole%String(i)%ComponentType=2
- if(item%ComponentType == 1) DownHole%String(i)%ComponentType=3
- !print*, 'item%ComponentType=', item%ComponentType
- !print*, 'String(i)%ComponentType=', String(i)%ComponentType
- !print*, 'String(i)%StartMd=', String(i)%StartMd
- !print*, 'String(i)%EndMd=', String(i)%EndMd
- !print*, '----------------------------'
-
- !call Log_3( 'item%ComponentType=', item%ComponentType)
- !call Log_3( 'String(i)%ComponentType=', String(i)%ComponentType)
- !call Log_3( 'String(i)%StartMd=', String(i)%StartMd)
- !call Log_3( 'String(i)%EndMd=', String(i)%EndMd)
- !call Log_3( '----------------------------')
-
- end do
- !!print*, '============CMP-ST============'
- !!call Log_3( '============CMP-ST============')
- !if(associated(StringComponentArrayPtr)) then
- ! call StringComponentArrayPtr(String)
- !end if
- end if
- end subroutine SetString
-
- subroutine SetBopElements(array)
- use CLog4
- implicit none
- integer, parameter :: count = 4
- integer :: i = 1 !, j
- type(CBopElement), intent(inout), target :: array(count)
- type(CBopElement), pointer :: item
- if(size(DownHole%BopElements) > 0) deallocate(DownHole%BopElements)
- allocate(DownHole%BopElements(count))
-
- do i = 1, count
- item => array(i)
- !call Log_4('item%ElementStart', item%ElementStart)
- !call Log_4('item%ElementEnd', item%ElementEnd)
- !call Log_4('item%ElementType', item%ElementType)
- !call Log_4('=====================================================')
-
- DownHole%BopElements(i)%ElementStart = item%ElementStart
- DownHole%BopElements(i)%ElementEnd = item%ElementEnd
- DownHole%BopElements(i)%ElementType = item%ElementType
- end do
-
- !if(associated(BopElementsPtr)) call BopElementsPtr(BopElements)
- end subroutine SetBopElements
-
- subroutine GetAnnalusFluidInfo(md)
- !DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidInfo
- !DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidInfo' :: GetAnnalusFluidInfo
- !use ElementFinderVars
- implicit none
- integer, intent(in) :: md
-
- call AnnulusPropertyCalculator(md, DownHole%Density, DownHole%Pressure, DownHole%Temperature)
-
- !ObservationPoint(2)%MeasureDepth = md
-
- !Density = md + Density - 10
- !Pressure = md + Pressure - 20
- !Temperature = md + Temperature - 30
- !Height = Height * 100.0
- !Volume = Volume * 200.0
- !
- !call Log_4('GetAnnalusFluidInfo=', md)
- !call Log_4('A_Height=', Height)
- !call Log_4('A_Volume=', Volume)
-
- #ifdef deb
- print*, 'GetAnnalusFluidInfo=', md
- #endif
-
- end subroutine GetAnnalusFluidInfo
-
- subroutine GetStringFluidInfo(md)
- !DEC$ ATTRIBUTES DLLEXPORT::GetStringFluidInfo
- !DEC$ ATTRIBUTES ALIAS: 'GetStringFluidInfo' :: GetStringFluidInfo
- implicit none
- integer, intent(in) :: md
-
- call StringPropertyCalculator(md, DownHole%Density, DownHole%Pressure, DownHole%Temperature)
-
- !ObservationPoint(1)%MeasureDepth = md
-
- !Density = md + Density + 100
- !Pressure = md + Pressure + 200
- !Temperature = md + Temperature + 300
- !Height = Height * 100.0
- !Volume = Volume * 200.0
- !
- !call Log_4('GetStringFluidInfo=', md)
- !call Log_4('S_Height=', Height)
- !call Log_4('S_Volume=', Volume)
-
- #ifdef deb
- print*, 'GetStringFluidInfo=', md
- #endif
- end subroutine GetStringFluidInfo
-
- end module CDownHoleVariables
|