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 DownHole%AnnDrillMud = .true. end subroutine AnnalusDrillMud subroutine AnnalusCirculateMud !DEC$ ATTRIBUTES DLLEXPORT::AnnalusCirculateMud !DEC$ ATTRIBUTES ALIAS: 'AnnalusCirculateMud' :: AnnalusCirculateMud implicit none DownHole%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(DownHole%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(DownHole%AnnalusFluids)) return do i = 1, count item => array(i) item%StartMd = DownHole%AnnalusFluids(i)%StartMd item%EndMd = DownHole%AnnalusFluids(i)%EndMd item%Density = DownHole%AnnalusFluids(i)%Density item%MudType = DownHole%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(DownHole%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(DownHole%StringFluids)) return do i = 1, count item => array(i) item%StartMd = DownHole%StringFluids(i)%StartMd item%EndMd = DownHole%StringFluids(i)%EndMd item%Density = DownHole%StringFluids(i)%Density item%MudType = DownHole%StringFluids(i)%MudType end do end subroutine GetStringFluids integer function GetStringCount() !DEC$ ATTRIBUTES DLLEXPORT::GetStringCount !DEC$ ATTRIBUTES ALIAS: 'GetStringCount' :: GetStringCount implicit none GetStringCount = DownHole%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(DownHole%BopElements) !Annalus if(associated(AnnalusMudCountPtr)) call AnnalusMudCountPtr(DownHole%AnnalusFluidsCount) if(associated(AnnalusMudArrayPtr)) call AnnalusMudArrayPtr(DownHole%AnnalusFluids) !string if(associated(StringMudCountPtr)) call StringMudCountPtr(DownHole%StringFluidsCount) if(associated(StringMudArrayPtr)) call StringMudArrayPtr(DownHole%StringFluids) !components if(associated(StringComponentCountPtr)) call StringComponentCountPtr(DownHole%StringCount) if(associated(StringComponentArrayPtr)) call StringComponentArrayPtr(DownHole%String) end subroutine GetDownhole real(8) function GetDrillPipePressureH() !DEC$ ATTRIBUTES DLLEXPORT :: GetDrillPipePressureH !DEC$ ATTRIBUTES ALIAS: 'GetDrillPipePressureH' :: GetDrillPipePressureH use PressureDisplayVARIABLES implicit none GetDrillPipePressureH = DownHole%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 = DownHole%CasingPressure end function real(8) function GetShoePressure() !DEC$ ATTRIBUTES DLLEXPORT :: GetShoePressure !DEC$ ATTRIBUTES ALIAS: 'GetShoePressure' :: GetShoePressure use PressureDisplayVARIABLES implicit none GetShoePressure = DownHole%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 = DownHole%BottomHolePressure !real(PressureGauges(3), 8) ! end function real(8) function GetFormationPressure() !DEC$ ATTRIBUTES DLLEXPORT :: GetFormationPressure !DEC$ ATTRIBUTES ALIAS: 'GetFormationPressure' :: GetFormationPressure implicit none GetFormationPressure = DownHole%FormationPressure end function real function GetInfluxRate() !DEC$ ATTRIBUTES DLLEXPORT :: GetInfluxRate !DEC$ ATTRIBUTES ALIAS: 'GetInfluxRate' :: GetInfluxRate implicit none GetInfluxRate = DownHole%InfluxRate end function real function GetKickVolume() !DEC$ ATTRIBUTES DLLEXPORT :: GetKickVolume !DEC$ ATTRIBUTES ALIAS: 'GetKickVolume' :: GetKickVolume implicit none !KickVolume = KickVolume + 1 GetKickVolume = DownHole%KickVolume end function real function GetSecondKickVolume() !DEC$ ATTRIBUTES DLLEXPORT :: GetSecondKickVolume !DEC$ ATTRIBUTES ALIAS: 'GetSecondKickVolume' :: GetSecondKickVolume implicit none !SecondKickVolume = SecondKickVolume + 1 GetSecondKickVolume = DownHole%SecondKickVolume end function real function GetPermeabilityExposedHeight() !DEC$ ATTRIBUTES DLLEXPORT :: GetPermeabilityExposedHeight !DEC$ ATTRIBUTES ALIAS: 'GetPermeabilityExposedHeight' :: GetPermeabilityExposedHeight implicit none GetPermeabilityExposedHeight = DownHole%PermeabilityExposedHeight end function real(8) function GetDensityH() !DEC$ ATTRIBUTES DLLEXPORT :: GetDensityH !DEC$ ATTRIBUTES ALIAS: 'GetDensityH' :: GetDensityH implicit none GetDensityH = DownHole%Density end function real(8) function GetPressureH() !DEC$ ATTRIBUTES DLLEXPORT :: GetPressureH !DEC$ ATTRIBUTES ALIAS: 'GetPressureH' :: GetPressureH implicit none GetPressureH = DownHole%Pressure end function real(8) function GetTemperatureH() !DEC$ ATTRIBUTES DLLEXPORT :: GetTemperatureH !DEC$ ATTRIBUTES ALIAS: 'GetTemperatureH' :: GetTemperatureH implicit none GetTemperatureH = DownHole%Temperature end function real(8) function GetHeightH() !DEC$ ATTRIBUTES DLLEXPORT :: GetHeightH !DEC$ ATTRIBUTES ALIAS: 'GetHeightH' :: GetHeightH implicit none GetHeightH = DownHole%Height end function real(8) function GetVolumeH() !DEC$ ATTRIBUTES DLLEXPORT :: GetVolumeH !DEC$ ATTRIBUTES ALIAS: 'GetVolumeH' :: GetVolumeH implicit none GetVolumeH = DownHole%Volume end function end module CDownHole