|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278 |
- module CDownHole
- use CDownHoleVariables
- implicit none
- public
-
- !abstract interface
- ! subroutine ActionFluid(array)
- ! use CDownHoleVariables
- ! type(CFluid), intent(inout), target :: array
- ! end subroutine
- !end interface
-
- contains
-
-
- subroutine AnnalusDrillMud
- !DEC$ ATTRIBUTES DLLEXPORT::AnnalusDrillMud
- !DEC$ ATTRIBUTES ALIAS: 'AnnalusDrillMud' :: AnnalusDrillMud
- implicit none
- AnnDrillMud = .true.
- end subroutine AnnalusDrillMud
-
- subroutine AnnalusCirculateMud
- !DEC$ ATTRIBUTES DLLEXPORT::AnnalusCirculateMud
- !DEC$ ATTRIBUTES ALIAS: 'AnnalusCirculateMud' :: AnnalusCirculateMud
- implicit none
- AnnCirculateMud = .true.
- end subroutine AnnalusCirculateMud
-
-
- !type(CFluid) function ActionFluid() !(array)
- ! !use CDownHoleVariables
- ! !integer, intent(in) :: count
- ! !type(CFluid), intent(inout), target :: array !(count)
- ! end function
-
-
- integer function GetAnnalusFluidsCount()
- !DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidsCount
- !DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidsCount' :: GetAnnalusFluidsCount
- implicit none
- GetAnnalusFluidsCount = size(AnnalusFluids)
- !GetAnnalusFluidsCount = AnnalusFluidsCount
- end function GetAnnalusFluidsCount
-
- subroutine GetAnnalusFluids(count, array)
- !DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluids
- !DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluids' :: GetAnnalusFluids
- implicit none
- integer :: i
- integer, intent(in) :: count
- type(CFluid), intent(inout), target :: array(count)
- type(CFluid), pointer :: item
- if(.not.allocated(AnnalusFluids)) return
- do i = 1, count
- item => array(i)
- item%StartMd = AnnalusFluids(i)%StartMd
- item%EndMd = AnnalusFluids(i)%EndMd
- item%Density = AnnalusFluids(i)%Density
- item%MudType = AnnalusFluids(i)%MudType
- end do
- end subroutine GetAnnalusFluids
-
-
- integer function GetStringFluidsCount()
- !DEC$ ATTRIBUTES DLLEXPORT::GetStringFluidsCount
- !DEC$ ATTRIBUTES ALIAS: 'GetStringFluidsCount' :: GetStringFluidsCount
- implicit none
- !GetStringFluidsCount = StringFluidsCount
- GetStringFluidsCount = size(StringFluids)
- end function GetStringFluidsCount
-
- subroutine GetStringFluids(count, array)
- !DEC$ ATTRIBUTES DLLEXPORT::GetStringFluids
- !DEC$ ATTRIBUTES ALIAS: 'GetStringFluids' :: GetStringFluids
- implicit none
- integer :: i
- integer, intent(in) :: count
- type(CFluid), intent(inout), target :: array(count)
- type(CFluid), pointer :: item
- if(.not.allocated(StringFluids)) return
- do i = 1, count
- item => array(i)
- item%StartMd = StringFluids(i)%StartMd
- item%EndMd = StringFluids(i)%EndMd
- item%Density = StringFluids(i)%Density
- item%MudType = StringFluids(i)%MudType
- end do
- end subroutine GetStringFluids
-
-
- integer function GetStringCount()
- !DEC$ ATTRIBUTES DLLEXPORT::GetStringCount
- !DEC$ ATTRIBUTES ALIAS: 'GetStringCount' :: GetStringCount
- implicit none
- GetStringCount = StringCount
- !GetStringCount = 4
- end function GetStringCount
-
- subroutine GetString(count, array)
- !DEC$ ATTRIBUTES DLLEXPORT::GetString
- !DEC$ ATTRIBUTES ALIAS: 'GetString' :: GetString
- implicit none
- integer :: i
- integer, intent(in) :: count
- type(CStringComponent), intent(inout), target :: array(count)
- type(CStringComponent), pointer :: item
- !do i = 1, count
- ! item => array(i)
- ! item%Length = String(i)%Length
- ! item%TopDepth = String(i)%TopDepth
- ! item%DownDepth = String(i)%DownDepth
- ! item%Od = String(i)%Od
- ! item%Id = String(i)%Id
- ! item%ComponentType = String(i)%ComponentType
- !end do
- end subroutine GetString
-
-
-
-
-
- subroutine GetDownhole()
- !DEC$ ATTRIBUTES DLLEXPORT::GetDownhole
- !DEC$ ATTRIBUTES ALIAS: 'GetDownhole' :: GetDownhole
- implicit none
-
- !BopElement
- if(associated(BopElementsPtr)) call BopElementsPtr(BopElements)
-
-
- !Annalus
- if(associated(AnnalusMudCountPtr)) call AnnalusMudCountPtr(AnnalusFluidsCount)
- if(associated(AnnalusMudArrayPtr)) call AnnalusMudArrayPtr(AnnalusFluids)
-
-
- !string
- if(associated(StringMudCountPtr)) call StringMudCountPtr(StringFluidsCount)
- if(associated(StringMudArrayPtr)) call StringMudArrayPtr(StringFluids)
-
-
- !components
- if(associated(StringComponentCountPtr)) call StringComponentCountPtr(StringCount)
- if(associated(StringComponentArrayPtr)) call StringComponentArrayPtr(String)
-
-
- end subroutine GetDownhole
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- real(8) function GetDrillPipePressureH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetDrillPipePressureH
- !DEC$ ATTRIBUTES ALIAS: 'GetDrillPipePressureH' :: GetDrillPipePressureH
- use PressureDisplayVARIABLES
- implicit none
- GetDrillPipePressureH = DrillPipePressure !real(PressureGauges(1), 8) !
- end function
-
- real(8) function GetCasingPressureH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressureH
- !DEC$ ATTRIBUTES ALIAS: 'GetCasingPressureH' :: GetCasingPressureH
- use FricPressDropVars
- implicit none
- !if (allocated(FinalFlowEl)) then
- ! if(size(FinalFlowEl) > 0) then
- ! CasingPressure = real(int(FinalFlowEl(AnnulusLastEl)%EndPress), 8) !CasingPressure
- ! endif
- !endif
- GetCasingPressureH = CasingPressure
- end function
-
- real(8) function GetShoePressure()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetShoePressure
- !DEC$ ATTRIBUTES ALIAS: 'GetShoePressure' :: GetShoePressure
- use PressureDisplayVARIABLES
- implicit none
- GetShoePressure = ShoePressure !real(PressureGauges(5), 8) !
- end function
-
- real(8) function GetBottomHolePressure()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetBottomHolePressure
- !DEC$ ATTRIBUTES ALIAS: 'GetBottomHolePressure' :: GetBottomHolePressure
- use PressureDisplayVARIABLES
- implicit none
- GetBottomHolePressure = BottomHolePressure !real(PressureGauges(3), 8) !
- end function
-
- real(8) function GetFormationPressure()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetFormationPressure
- !DEC$ ATTRIBUTES ALIAS: 'GetFormationPressure' :: GetFormationPressure
- implicit none
- GetFormationPressure = FormationPressure
- end function
-
- real function GetInfluxRate()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetInfluxRate
- !DEC$ ATTRIBUTES ALIAS: 'GetInfluxRate' :: GetInfluxRate
- implicit none
- GetInfluxRate = InfluxRate
- end function
-
- real function GetKickVolume()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetKickVolume
- !DEC$ ATTRIBUTES ALIAS: 'GetKickVolume' :: GetKickVolume
- implicit none
-
- !KickVolume = KickVolume + 1
-
- GetKickVolume = KickVolume
- end function
-
- real function GetSecondKickVolume()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSecondKickVolume
- !DEC$ ATTRIBUTES ALIAS: 'GetSecondKickVolume' :: GetSecondKickVolume
- implicit none
-
- !SecondKickVolume = SecondKickVolume + 1
-
- GetSecondKickVolume = SecondKickVolume
- end function
-
- real function GetPermeabilityExposedHeight()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetPermeabilityExposedHeight
- !DEC$ ATTRIBUTES ALIAS: 'GetPermeabilityExposedHeight' :: GetPermeabilityExposedHeight
- implicit none
- GetPermeabilityExposedHeight = PermeabilityExposedHeight
- end function
-
-
-
- real(8) function GetDensityH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetDensityH
- !DEC$ ATTRIBUTES ALIAS: 'GetDensityH' :: GetDensityH
- implicit none
- GetDensityH = Density
- end function
-
- real(8) function GetPressureH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetPressureH
- !DEC$ ATTRIBUTES ALIAS: 'GetPressureH' :: GetPressureH
- implicit none
- GetPressureH = Pressure
- end function
-
- real(8) function GetTemperatureH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTemperatureH
- !DEC$ ATTRIBUTES ALIAS: 'GetTemperatureH' :: GetTemperatureH
- implicit none
- GetTemperatureH = Temperature
- end function
-
-
- real(8) function GetHeightH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetHeightH
- !DEC$ ATTRIBUTES ALIAS: 'GetHeightH' :: GetHeightH
- implicit none
- GetHeightH = Height
- end function
-
- real(8) function GetVolumeH()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetVolumeH
- !DEC$ ATTRIBUTES ALIAS: 'GetVolumeH' :: GetVolumeH
- implicit none
- GetVolumeH = Volume
- end function
-
- end module CDownHole
|