@@ -1,237 +0,0 @@ | |||||
module CMudProperties | |||||
use CMudPropertiesVariables | |||||
use CLog4 | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetActiveMudType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveMudType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveMudType' :: SetActiveMudType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MudProperties%ActiveMudType = v | |||||
end subroutine | |||||
subroutine SetActiveRheologyModel(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveRheologyModel | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveRheologyModel' :: SetActiveRheologyModel | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MudProperties%ActiveRheologyModel = v | |||||
#ifdef deb | |||||
call Log_4( '=====ActiveRheologyModel=', MudProperties%ActiveRheologyModel) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveMudVolume' :: SetActiveMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveMudVolume = v | |||||
!call Log_5('ActiveDensity=', ActiveDensity) | |||||
#ifdef deb | |||||
print*, 'ActiveMudVolume=', MudProperties%ActiveMudVolume | |||||
#endif | |||||
MudProperties%ActiveMudVolumeGal = v * 42.0 | |||||
call OnActiveMudVolumeChange%RunAll(v * 42.0d0) | |||||
end subroutine | |||||
subroutine SetActiveDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveDensity' :: SetActiveDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveDensity = v | |||||
!call Log_5('ActiveDensity=', ActiveDensity) | |||||
#ifdef deb | |||||
print*, 'ActiveDensity=', MudProperties%ActiveDensity | |||||
#endif | |||||
call OnActiveDensityChange%RunAll(v) | |||||
end subroutine | |||||
subroutine SetActiveThetaThreeHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveThetaThreeHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveThetaThreeHundred' :: SetActiveThetaThreeHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveThetaThreeHundred = v | |||||
end subroutine | |||||
subroutine SetActiveThetaSixHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveThetaSixHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveThetaSixHundred' :: SetActiveThetaSixHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveThetaSixHundred = v | |||||
end subroutine | |||||
subroutine SetReserveMudType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveMudType' :: SetReserveMudType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MudProperties%ReserveMudType = v | |||||
end subroutine | |||||
subroutine SetReserveMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveMudVolume' :: SetReserveMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReserveMudVolume = v | |||||
!call Log_5('ReserveMudVolume=', ReserveMudVolume) | |||||
#ifdef deb | |||||
print*, 'ReserveMudVolume=', MudProperties%ReserveMudVolume | |||||
#endif | |||||
MudProperties%ReserveMudVolumeGal = v * 42.0 | |||||
call OnReserveMudVolumeChange%RunAll(v * 42.0d0) | |||||
end subroutine | |||||
subroutine SetReserveDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveDensity' :: SetReserveDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReserveDensity = v | |||||
!call Log_5('ReserveDensity=', ReserveDensity) | |||||
#ifdef deb | |||||
print*, 'ReserveDensity=', MudProperties%ReserveDensity | |||||
#endif | |||||
call OnReserveDensityChange%RunAll(v) | |||||
end subroutine | |||||
subroutine SetReserveThetaThreeHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveThetaThreeHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveThetaThreeHundred' :: SetReserveThetaThreeHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReserveThetaThreeHundred = v | |||||
end subroutine | |||||
subroutine SetReserveThetaSixHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveThetaSixHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveThetaSixHundred' :: SetReserveThetaSixHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReserveThetaSixHundred = v | |||||
end subroutine | |||||
subroutine SetActiveTotalTankCapacity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalTankCapacity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalTankCapacity' :: SetActiveTotalTankCapacity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveTotalTankCapacity = v | |||||
MudProperties%ActiveTotalTankCapacityGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveTotalTankCapacity=', MudProperties%ActiveTotalTankCapacity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveSettledContents(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveSettledContents | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveSettledContents' :: SetActiveSettledContents | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveSettledContents = v | |||||
MudProperties%ActiveSettledContentsGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveSettledContents=', MudProperties%ActiveSettledContents | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveTotalContents(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalContents | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalContents' :: SetActiveTotalContents | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveTotalContents = v | |||||
MudProperties%ActiveTotalContentsGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveTotalContents=', MudProperties%ActiveTotalContents | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActivePlasticViscosity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActivePlasticViscosity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActivePlasticViscosity' :: SetActivePlasticViscosity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActivePlasticViscosity = v | |||||
#ifdef deb | |||||
print*, 'ActivePlasticViscosity=', MudProperties%ActivePlasticViscosity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveYieldPoint(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveYieldPoint | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveYieldPoint' :: SetActiveYieldPoint | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ActiveYieldPoint = v | |||||
#ifdef deb | |||||
print*, 'ActiveYieldPoint=', MudProperties%ActiveYieldPoint | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveAutoDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveAutoDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveAutoDensity' :: SetActiveAutoDensity | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MudProperties%ActiveAutoDensity = v | |||||
#ifdef deb | |||||
print*, 'ActiveAutoDensity=', MudProperties%ActiveAutoDensity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetReservePlasticViscosity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReservePlasticViscosity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReservePlasticViscosity' :: SetReservePlasticViscosity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReservePlasticViscosity = v | |||||
#ifdef deb | |||||
print*, 'ReservePlasticViscosity=', MudProperties%ReservePlasticViscosity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetReserveYieldPoint(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveYieldPoint | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveYieldPoint' :: SetReserveYieldPoint | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%ReserveYieldPoint = v | |||||
#ifdef deb | |||||
print*, 'ReserveYieldPoint=', MudProperties%ReserveYieldPoint | |||||
#endif | |||||
end subroutine | |||||
subroutine SetInitialTripTankMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetInitialTripTankMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetInitialTripTankMudVolume' :: SetInitialTripTankMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%InitialTripTankMudVolume = v | |||||
MudProperties%InitialTripTankMudVolumeGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'InitialTripTankMudVolume=', MudProperties%InitialTripTankMudVolume | |||||
#endif | |||||
end subroutine | |||||
subroutine SetPedalFlowMeter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPedalFlowMeter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPedalFlowMeter' :: SetPedalFlowMeter | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudProperties%PedalFlowMeter = v | |||||
#ifdef deb | |||||
print*, 'PedalFlowMeter=', MudProperties%PedalFlowMeter | |||||
#endif | |||||
end subroutine | |||||
end module CMudProperties |
@@ -1,19 +1,19 @@ | |||||
module CMudPropertiesVariables | module CMudPropertiesVariables | ||||
use CIActionReference | use CIActionReference | ||||
use CDoubleEventHandlerCollection | |||||
!**use CDoubleEventHandlerCollection | |||||
implicit none | implicit none | ||||
public | public | ||||
!pointers | !pointers | ||||
procedure (ActionDouble), pointer :: ActiveMudVolumePtr | |||||
procedure (ActionDouble), pointer :: ActiveDensityPtr | |||||
procedure (ActionDouble), pointer :: ReserveMudVolumePtr | |||||
procedure (ActionDouble), pointer :: ReserveDensityPtr | |||||
! procedure (ActionDouble), pointer :: ActiveMudVolumePtr | |||||
! procedure (ActionDouble), pointer :: ActiveDensityPtr | |||||
! procedure (ActionDouble), pointer :: ReserveMudVolumePtr | |||||
! procedure (ActionDouble), pointer :: ReserveDensityPtr | |||||
type(DoubleEventHandlerCollection) :: OnActiveMudVolumeChange | |||||
type(DoubleEventHandlerCollection) :: OnActiveDensityChange | |||||
type(DoubleEventHandlerCollection) :: OnReserveMudVolumeChange | |||||
type(DoubleEventHandlerCollection) :: OnReserveDensityChange | |||||
!**type(DoubleEventHandlerCollection) :: OnActiveMudVolumeChange | |||||
!**type(DoubleEventHandlerCollection) :: OnActiveDensityChange | |||||
!**type(DoubleEventHandlerCollection) :: OnReserveMudVolumeChange | |||||
!**type(DoubleEventHandlerCollection) :: OnReserveDensityChange | |||||
!constants | !constants | ||||
integer, parameter :: WaterBase_MudType = 0 | integer, parameter :: WaterBase_MudType = 0 | ||||
@@ -73,7 +73,7 @@ module CMudPropertiesVariables | |||||
if(MudProperties%ActiveMudVolume == v) return | if(MudProperties%ActiveMudVolume == v) return | ||||
#endif | #endif | ||||
MudProperties%ActiveMudVolume = v | MudProperties%ActiveMudVolume = v | ||||
if(associated(ActiveMudVolumePtr)) call ActiveMudVolumePtr(MudProperties%ActiveMudVolume) | |||||
! if(associated(ActiveMudVolumePtr)) call ActiveMudVolumePtr(MudProperties%ActiveMudVolume) | |||||
end subroutine | end subroutine | ||||
subroutine Set_ActiveDensity_StudentStation(v) | subroutine Set_ActiveDensity_StudentStation(v) | ||||
@@ -83,7 +83,7 @@ module CMudPropertiesVariables | |||||
if(MudProperties%ActiveDensity == v) return | if(MudProperties%ActiveDensity == v) return | ||||
#endif | #endif | ||||
MudProperties%ActiveDensity = v | MudProperties%ActiveDensity = v | ||||
if(associated(ActiveDensityPtr)) call ActiveDensityPtr(MudProperties%ActiveDensity) | |||||
! if(associated(ActiveDensityPtr)) call ActiveDensityPtr(MudProperties%ActiveDensity) | |||||
end subroutine | end subroutine | ||||
subroutine Set_ReserveMudVolume_StudentStation(v) | subroutine Set_ReserveMudVolume_StudentStation(v) | ||||
@@ -93,7 +93,7 @@ module CMudPropertiesVariables | |||||
if(MudProperties%ReserveMudVolume == v) return | if(MudProperties%ReserveMudVolume == v) return | ||||
#endif | #endif | ||||
MudProperties%ReserveMudVolume = v | MudProperties%ReserveMudVolume = v | ||||
if(associated(ReserveMudVolumePtr)) call ReserveMudVolumePtr(MudProperties%ReserveMudVolume) | |||||
! if(associated(ReserveMudVolumePtr)) call ReserveMudVolumePtr(MudProperties%ReserveMudVolume) | |||||
end subroutine | end subroutine | ||||
subroutine Set_ReserveDensity_StudentStation(v) | subroutine Set_ReserveDensity_StudentStation(v) | ||||
@@ -103,41 +103,41 @@ module CMudPropertiesVariables | |||||
if(MudProperties%ReserveDensity == v) return | if(MudProperties%ReserveDensity == v) return | ||||
#endif | #endif | ||||
MudProperties%ReserveDensity = v | MudProperties%ReserveDensity = v | ||||
if(associated(ReserveDensityPtr)) call ReserveDensityPtr(MudProperties%ReserveDensity) | |||||
! if(associated(ReserveDensityPtr)) call ReserveDensityPtr(MudProperties%ReserveDensity) | |||||
end subroutine | end subroutine | ||||
subroutine SubscribeActiveMudVolume(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveMudVolume' :: SubscribeActiveMudVolume | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
ActiveMudVolumePtr => a | |||||
end subroutine | |||||
! subroutine SubscribeActiveMudVolume(a) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveMudVolume | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveMudVolume' :: SubscribeActiveMudVolume | |||||
! implicit none | |||||
! procedure (ActionDouble) :: a | |||||
! ActiveMudVolumePtr => a | |||||
! end subroutine | |||||
subroutine SubscribeActiveDensity(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveDensity' :: SubscribeActiveDensity | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
ActiveDensityPtr => a | |||||
end subroutine | |||||
! subroutine SubscribeActiveDensity(a) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveDensity | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveDensity' :: SubscribeActiveDensity | |||||
! implicit none | |||||
! procedure (ActionDouble) :: a | |||||
! ActiveDensityPtr => a | |||||
! end subroutine | |||||
subroutine SubscribeReserveMudVolume(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveMudVolume' :: SubscribeReserveMudVolume | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
ReserveMudVolumePtr => a | |||||
end subroutine | |||||
! subroutine SubscribeReserveMudVolume(a) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveMudVolume | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveMudVolume' :: SubscribeReserveMudVolume | |||||
! implicit none | |||||
! procedure (ActionDouble) :: a | |||||
! ReserveMudVolumePtr => a | |||||
! end subroutine | |||||
subroutine SubscribeReserveDensity(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveDensity' :: SubscribeReserveDensity | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
ReserveDensityPtr => a | |||||
end subroutine | |||||
! subroutine SubscribeReserveDensity(a) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveDensity | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveDensity' :: SubscribeReserveDensity | |||||
! implicit none | |||||
! procedure (ActionDouble) :: a | |||||
! ReserveDensityPtr => a | |||||
! end subroutine | |||||
end module CMudPropertiesVariables | end module CMudPropertiesVariables |
@@ -2,50 +2,47 @@ module CCommon | |||||
use CCommonVariables | use CCommonVariables | ||||
implicit none | implicit none | ||||
public | public | ||||
contains | |||||
contains | |||||
! Input routines | ! Input routines | ||||
subroutine SetStandRack(v) | subroutine SetStandRack(v) | ||||
implicit none | implicit none | ||||
integer, intent(in) :: v | integer, intent(in) :: v | ||||
if(Common%StandRack == v) return | if(Common%StandRack == v) return | ||||
Common%StandRack = v | Common%StandRack = v | ||||
call Common%OnStandRackChange%Run(v) | |||||
#ifdef deb | |||||
print*, 'StandRack=', Common%StandRack | |||||
#endif | |||||
! call Common%OnStandRackChange%Run(v) | |||||
end subroutine | end subroutine | ||||
integer function GetStandRack() | |||||
implicit none | |||||
GetStandRack = Common%StandRack | |||||
end function | |||||
subroutine SetStandRack_WN(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandRack_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandRack_WN' :: SetStandRack_WN | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
call SetStandRack(v) | |||||
end subroutine | |||||
! subroutine SetStandRack_WN(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetStandRack_WN | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetStandRack_WN' :: SetStandRack_WN | |||||
! implicit none | |||||
! integer, intent(in) :: v | |||||
! call SetStandRack(v) | |||||
! end subroutine | |||||
! Output routines | |||||
logical function GetDrillWatchOperationMode() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDrillWatchOperationMode | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDrillWatchOperationMode' :: GetDrillWatchOperationMode | |||||
implicit none | |||||
GetDrillWatchOperationMode = Common%DrillWatchOperationMode | |||||
end function | |||||
! ! Output routines | |||||
! logical function GetDrillWatchOperationMode() | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: GetDrillWatchOperationMode | |||||
! !DEC$ ATTRIBUTES ALIAS: 'GetDrillWatchOperationMode' :: GetDrillWatchOperationMode | |||||
! implicit none | |||||
! GetDrillWatchOperationMode = Common%DrillWatchOperationMode | |||||
! end function | |||||
integer function GetStandRack() | |||||
implicit none | |||||
GetStandRack = Common%StandRack | |||||
end function | |||||
integer function GetStandRack_WN() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandRack_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandRack_WN' :: GetStandRack_WN | |||||
implicit none | |||||
GetStandRack_WN = Common%StandRack | |||||
end function | |||||
! integer function GetStandRack_WN() | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: GetStandRack_WN | |||||
! !DEC$ ATTRIBUTES ALIAS: 'GetStandRack_WN' :: GetStandRack_WN | |||||
! implicit none | |||||
! GetStandRack_WN = Common%StandRack | |||||
! end function | |||||
@@ -1,15 +1,16 @@ | |||||
module CCommonVariables | module CCommonVariables | ||||
use CIntegerEventHandler | |||||
!**use CIntegerEventHandler | |||||
implicit none | implicit none | ||||
public | public | ||||
type :: CommonType | type :: CommonType | ||||
! Input vars | ! Input vars | ||||
integer :: StandRack | integer :: StandRack | ||||
type(IntegerEventHandler) :: OnStandRackChange | |||||
! type(IntegerEventHandler) :: OnStandRackChange | |||||
! Output vars | ! Output vars | ||||
logical :: DrillWatchOperationMode | logical :: DrillWatchOperationMode | ||||
end type | end type | ||||
type(CommonType):: Common | type(CommonType):: Common | ||||
contains | contains | ||||
end module CCommonVariables | end module CCommonVariables |
@@ -1,44 +0,0 @@ | |||||
module CBoolEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: BoolEventHandler | |||||
procedure(ActionBool), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type BoolEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
procedure (ActionBool), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(BoolEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
logical, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CBoolEventHandler |
@@ -1,103 +0,0 @@ | |||||
module CBoolEventHandlerCollection | |||||
use CBoolEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: BoolEventHandlerCollection | |||||
type(BoolEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type BoolEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
type(BoolEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionBool), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(BoolEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
logical, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CBoolEventHandlerCollection |
@@ -1,43 +0,0 @@ | |||||
module CDoubleEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: DoubleEventHandler | |||||
procedure(ActionDouble), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type DoubleEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
procedure (ActionDouble), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
real(8), intent(in) :: arg | |||||
if(.not.this%IsNull()) call this%Delegate(arg) | |||||
end subroutine | |||||
end module CDoubleEventHandler |
@@ -1,103 +0,0 @@ | |||||
module CDoubleEventHandlerCollection | |||||
use CDoubleEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: DoubleEventHandlerCollection | |||||
type(DoubleEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type DoubleEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
type(DoubleEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionDouble), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(DoubleEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
real(8), intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CDoubleEventHandlerCollection |
@@ -1,44 +0,0 @@ | |||||
module CIntegerArrayEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: IntegerArrayEventHandler | |||||
procedure(ActionIntegerArray), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type IntegerArrayEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
procedure (ActionIntegerArray), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
integer, allocatable, intent (in) :: arg(:) | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CIntegerArrayEventHandler |
@@ -1,103 +0,0 @@ | |||||
module CIntegerArrayEventHandlerCollection | |||||
use CIntegerArrayEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: IntegerArrayEventHandlerCollection | |||||
type(IntegerArrayEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll_ | |||||
end type IntegerArrayEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
type(IntegerArrayEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionIntegerArray), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(IntegerArrayEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll_(this, arg) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
integer, allocatable, intent (in) :: arg(:) | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CIntegerArrayEventHandlerCollection |
@@ -1,44 +0,0 @@ | |||||
module CIntegerEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: IntegerEventHandler | |||||
procedure(ActionInteger), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type IntegerEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
procedure (ActionInteger), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
integer, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CIntegerEventHandler |
@@ -1,103 +0,0 @@ | |||||
module CIntegerEventHandlerCollection | |||||
use CIntegerEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: IntegerEventHandlerCollection | |||||
type(IntegerEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type IntegerEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
type(IntegerEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionInteger), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(IntegerEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CIntegerEventHandlerCollection |
@@ -1,44 +0,0 @@ | |||||
module CRealEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: RealEventHandler | |||||
procedure(ActionReal), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type RealEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
procedure (ActionReal), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(RealEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
real, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CRealEventHandler |
@@ -1,103 +0,0 @@ | |||||
module CRealEventHandlerCollection | |||||
use CRealEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: RealEventHandlerCollection | |||||
type(RealEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type RealEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
type(RealEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionReal), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(RealEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
real, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CRealEventHandlerCollection |
@@ -1,44 +0,0 @@ | |||||
module CVoidEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: VoidEventHandler | |||||
procedure(ActionVoid), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type VoidEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
procedure (ActionVoid), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
!if(.not.this%IsNull()) then | |||||
call this%Delegate() | |||||
!endif | |||||
end subroutine | |||||
end module CVoidEventHandler |
@@ -1,102 +0,0 @@ | |||||
module CVoidEventHandlerCollection | |||||
use CVoidEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: VoidEventHandlerCollection | |||||
type(VoidEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type VoidEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
type(VoidEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionVoid), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(VoidEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run() | |||||
end do | |||||
end subroutine | |||||
end module CVoidEventHandlerCollection |
@@ -5,6 +5,9 @@ module CDownHoleVariables | |||||
use CLog4 | use CLog4 | ||||
implicit none | implicit none | ||||
public | public | ||||
!!!!!!!!!!!!!!!!!!!!! | |||||
! Outputs to user interface | |||||
!!!!!!!!!!!!!!!!!!!!! | |||||
type :: DownHoleType | type :: DownHoleType | ||||
logical :: AnnDrillMud | logical :: AnnDrillMud | ||||
logical :: AnnCirculateMud | logical :: AnnCirculateMud | ||||
@@ -1,6 +1,6 @@ | |||||
module CDataDisplayConsoleVariables | module CDataDisplayConsoleVariables | ||||
use CIActionReference | use CIActionReference | ||||
use CDoubleEventHandlerCollection | |||||
! !**use CDoubleEventHandlerCollection | |||||
implicit none | implicit none | ||||
public | public | ||||
@@ -66,7 +66,7 @@ module CDataDisplayConsoleVariables | |||||
real(8) :: ReturnLineTempGauge | real(8) :: ReturnLineTempGauge | ||||
real(8) :: RotaryTorqueGauge | real(8) :: RotaryTorqueGauge | ||||
real(8) :: RotaryRPMGauge | real(8) :: RotaryRPMGauge | ||||
type(DoubleEventHandlerCollection) :: OnRotaryRpmChange | |||||
! !**type(DoubleEventHandlerCollection) :: OnRotaryRpmChange | |||||
integer :: AcidGasDetectionLED | integer :: AcidGasDetectionLED | ||||
real(8) :: TotalStrokeCounter | real(8) :: TotalStrokeCounter | ||||
!real(8) :: TotalStrokeCounter_temp | !real(8) :: TotalStrokeCounter_temp | ||||
@@ -221,7 +221,7 @@ module CDataDisplayConsoleVariables | |||||
DataDisplayConsole%RotaryRPMGauge = v | DataDisplayConsole%RotaryRPMGauge = v | ||||
DrillingWatch%RPM = v | DrillingWatch%RPM = v | ||||
DataDisplayConsole%RTRPM = v | DataDisplayConsole%RTRPM = v | ||||
call DataDisplayConsole%OnRotaryRpmChange%RunAll(v) | |||||
! call DataDisplayConsole%OnRotaryRpmChange%RunAll(v) | |||||
end subroutine | end subroutine | ||||
@@ -1,6 +1,6 @@ | |||||
module CDrillingConsoleVariables | module CDrillingConsoleVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
public | public | ||||
@@ -33,9 +33,9 @@ module CDrillingConsoleVariables | |||||
real(8) :: DWPowerLever | real(8) :: DWPowerLever | ||||
real(8) :: TongLever | real(8) :: TongLever | ||||
! type(VoidEventHandlerCollection) :: OnBreakoutLeverPress | |||||
! type(VoidEventHandlerCollection) :: OnMakeupLeverPress | |||||
! type(VoidEventHandlerCollection) :: OnTongNeutralPress | |||||
! ! type(VoidEventHandlerCollection) :: OnBreakoutLeverPress | |||||
! ! type(VoidEventHandlerCollection) :: OnMakeupLeverPress | |||||
! ! type(VoidEventHandlerCollection) :: OnTongNeutralPress | |||||
real(8) :: RTTransmissionLever | real(8) :: RTTransmissionLever | ||||
real(8) :: DWClutchLever | real(8) :: DWClutchLever | ||||
@@ -47,11 +47,11 @@ module CDrillingConsoleVariables | |||||
logical :: GEN4 | logical :: GEN4 | ||||
logical :: Permission_OpenKellyCock = .false. | logical :: Permission_OpenKellyCock = .false. | ||||
logical :: OpenKellyCock | logical :: OpenKellyCock | ||||
! type(VoidEventHandlerCollection) :: OnOpenKellyCockPress | |||||
! ! type(VoidEventHandlerCollection) :: OnOpenKellyCockPress | |||||
logical :: Permission_CloseKellyCock = .false. | logical :: Permission_CloseKellyCock = .false. | ||||
logical :: CloseKellyCock | logical :: CloseKellyCock | ||||
! type(VoidEventHandlerCollection) :: OnCloseKellyCockPress | |||||
! ! type(VoidEventHandlerCollection) :: OnCloseKellyCockPress | |||||
logical :: Permission_OpenSafetyValve = .false. | logical :: Permission_OpenSafetyValve = .false. | ||||
logical :: OpenSafetyValve | logical :: OpenSafetyValve | ||||
@@ -1,11 +1,11 @@ | |||||
module CHookVariables | module CHookVariables | ||||
use CRealEventHandlerCollection | |||||
!**use CRealEventHandlerCollection | |||||
! use CHookActions | ! use CHookActions | ||||
implicit none | implicit none | ||||
Type :: HookType | Type :: HookType | ||||
real :: HookHeight_S = 0.0 | real :: HookHeight_S = 0.0 | ||||
real :: HookHeight | real :: HookHeight | ||||
type(RealEventHandlerCollection) :: OnHookHeightChange | |||||
!**type(RealEventHandlerCollection) :: OnHookHeightChange | |||||
end type HookType | end type HookType | ||||
Type(HookType)::Hook | Type(HookType)::Hook | ||||
@@ -29,7 +29,7 @@ module CHookVariables | |||||
print*, 'HookHeight=', Hook%HookHeight | print*, 'HookHeight=', Hook%HookHeight | ||||
#endif | #endif | ||||
call Hook%OnHookHeightChange%RunAll(Hook%HookHeight) | |||||
!**call Hook%OnHookHeightChange%RunAll(Hook%HookHeight) | |||||
end subroutine | end subroutine | ||||
@@ -1,7 +1,7 @@ | |||||
module CManifolds | module CManifolds | ||||
use CStack | use CStack | ||||
use CArrangement | use CArrangement | ||||
use CPathChangeEvents | |||||
! use CPathChangeEvents | |||||
use CDrillingConsoleVariables!, only: DrillingConsole%IRSafetyValveLed, DrillingConsole%IRIBopLed, DrillingConsole%OpenKellyCockLed, DrillingConsole%CloseKellyCockLed, DrillingConsole%OpenSafetyValveLed, DrillingConsole%CloseSafetyValveLed | use CDrillingConsoleVariables!, only: DrillingConsole%IRSafetyValveLed, DrillingConsole%IRIBopLed, DrillingConsole%OpenKellyCockLed, DrillingConsole%CloseKellyCockLed, DrillingConsole%OpenSafetyValveLed, DrillingConsole%CloseSafetyValveLed | ||||
implicit none | implicit none | ||||
@@ -44,9 +44,9 @@ module CManifolds | |||||
call Setup() | call Setup() | ||||
!call OnSimulationInitialization%Add(PathFinding_Init) | !call OnSimulationInitialization%Add(PathFinding_Init) | ||||
!call OnSimulationStop%Add(PathFinding_Init) | !call OnSimulationStop%Add(PathFinding_Init) | ||||
!call OnPathFindingStep%Add(PathFinding_Step) | |||||
!call OnPathFindingOutput%Add(PathFinding_Output) | |||||
! call OnPathFindingMain%Add(PathFindingMainBody) | |||||
!!**call OnpPathFindingStep%Add(PathFinding_Step) | |||||
!!**call OnpPathFindingOutput%Add(PathFinding_Output) | |||||
! !**call OnpPathFindingMain%Add(PathFindingMainBody) | |||||
end subroutine | end subroutine | ||||
subroutine PathFinding_Init | subroutine PathFinding_Init | ||||
@@ -86,7 +86,7 @@ end subroutine PathFinding_Step | |||||
integer, dimension(8) :: StartTime,EndTime !TODO: clean up | integer, dimension(8) :: StartTime,EndTime !TODO: clean up | ||||
call DATE_AND_TIME(values=StartTime) !TODO: clean up | call DATE_AND_TIME(values=StartTime) !TODO: clean up | ||||
call BeforeTraverse%RunAll() | |||||
!**call BeforeTraverse%RunAll() | |||||
if(allocated(Manifold%OpenPaths)) deallocate(Manifold%OpenPaths) | if(allocated(Manifold%OpenPaths)) deallocate(Manifold%OpenPaths) | ||||
@@ -99,7 +99,7 @@ end subroutine PathFinding_Step | |||||
call PostProcess(Manifold%OpenPaths) | call PostProcess(Manifold%OpenPaths) | ||||
call AfterTraverse%RunAll() | |||||
!**call AfterTraverse%RunAll() | |||||
Manifold%IsTraverse = .true. | Manifold%IsTraverse = .true. | ||||
@@ -189,7 +189,7 @@ end subroutine PathFinding_Step | |||||
if(p%IsNull()) return | if(p%IsNull()) return | ||||
if(p%Length()<=1) return | if(p%Length()<=1) return | ||||
call OnPathOpen%RunAll(p%Valves) | |||||
!**call OnpPathOpen%RunAll(p%Valves) | |||||
if(allocated(pathArr)) then | if(allocated(pathArr)) then | ||||
isize = size(pathArr) | isize = size(pathArr) | ||||
@@ -253,7 +253,7 @@ end subroutine PathFinding_Step | |||||
end if | end if | ||||
if(found) then | if(found) then | ||||
tempArr(i-1) = pathArr(i) | tempArr(i-1) = pathArr(i) | ||||
!call OnPathClose%RunAll(pathArr(i)%Valves) | |||||
!!**call OnpPathClose%RunAll(pathArr(i)%Valves) | |||||
else | else | ||||
tempArr(i) = pathArr(i) | tempArr(i) = pathArr(i) | ||||
endif | endif | ||||
@@ -102,11 +102,11 @@ module COperationScenariosVariables | |||||
!moved from enum/CElevatorConnectionEnum | !moved from enum/CElevatorConnectionEnum | ||||
integer :: ElevatorConnection = 0 | integer :: ElevatorConnection = 0 | ||||
type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||||
! type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||||
!moved from SoftwareOutputs/CStringUpdateVariables | !moved from SoftwareOutputs/CStringUpdateVariables | ||||
integer :: StringUpdate = 0 | integer :: StringUpdate = 0 | ||||
type(IntegerEventHandlerCollection) :: OnStringUpdateChange | |||||
!**type(IntegerEventHandlerCollection) :: OnStringUpdateChange | |||||
end type OperationScenarioType | end type OperationScenarioType | ||||
@@ -130,7 +130,7 @@ module COperationScenariosVariables | |||||
if(OperationScenario%StringUpdate == v) return | if(OperationScenario%StringUpdate == v) return | ||||
#endif | #endif | ||||
OperationScenario%StringUpdate = v | OperationScenario%StringUpdate = v | ||||
call OperationScenario%OnStringUpdateChange%RunAll(v) | |||||
!**call OperationScenario%OnStringUpdateChange%RunAll(v) | |||||
end subroutine | end subroutine | ||||
integer function Get_StringUpdate() | integer function Get_StringUpdate() | ||||
@@ -166,7 +166,7 @@ module COperationScenariosVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'OperationScenario%ElevatorConnection=', OperationScenario%ElevatorConnection | print*, 'OperationScenario%ElevatorConnection=', OperationScenario%ElevatorConnection | ||||
#endif | #endif | ||||
call OperationScenario%OnElevatorConnectionChange%RunAll() | |||||
!**call OperationScenario%OnElevatorConnectionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_ElevatorConnection() | integer function Get_ElevatorConnection() | ||||
@@ -3,7 +3,7 @@ module CElevatorConnectionEnumVariables | |||||
implicit none | implicit none | ||||
! Mahmood: this variable moved to operationscenariocommon | ! Mahmood: this variable moved to operationscenariocommon | ||||
! integer :: OperationScenario%ElevatorConnection = 0 | ! integer :: OperationScenario%ElevatorConnection = 0 | ||||
! type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||||
! ! type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||||
public | public | ||||
@@ -1,9 +1,9 @@ | |||||
module CKellyConnectionEnumVariables | module CKellyConnectionEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
type::KellyConnectionEnumType | type::KellyConnectionEnumType | ||||
integer :: KellyConnection = 0 | integer :: KellyConnection = 0 | ||||
type(VoidEventHandlerCollection) :: OnKellyConnectionChange | |||||
! type(VoidEventHandlerCollection) :: OnKellyConnectionChange | |||||
end type KellyConnectionEnumType | end type KellyConnectionEnumType | ||||
type(KellyConnectionEnumType)::KellyConnectionEnum | type(KellyConnectionEnumType)::KellyConnectionEnum | ||||
! public | ! public | ||||
@@ -37,7 +37,7 @@ module CKellyConnectionEnumVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'KellyConnectionEnum%KellyConnection=', KellyConnectionEnum%KellyConnection | print*, 'KellyConnectionEnum%KellyConnection=', KellyConnectionEnum%KellyConnection | ||||
#endif | #endif | ||||
call KellyConnectionEnum%OnKellyConnectionChange%RunAll() | |||||
!**call KellyConnectionEnum%OnKellyConnectionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_KellyConnection() | integer function Get_KellyConnection() | ||||
@@ -1,9 +1,9 @@ | |||||
module CTdsConnectionModesEnumVariables | module CTdsConnectionModesEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
type:: TdsConnectionModesEnumType | type:: TdsConnectionModesEnumType | ||||
integer :: TdsConnectionModes = 0 | integer :: TdsConnectionModes = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsConnectionModesChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsConnectionModesChange | |||||
end type TdsConnectionModesEnumType | end type TdsConnectionModesEnumType | ||||
type(TdsConnectionModesEnumType)::TdsConnectionModesEnum | type(TdsConnectionModesEnumType)::TdsConnectionModesEnum | ||||
enum, bind(c) | enum, bind(c) | ||||
@@ -33,7 +33,7 @@ module CTdsConnectionModesEnumVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsConnectionModesEnum%TdsConnectionModes=', TdsConnectionModesEnum%TdsConnectionModes | print*, 'TdsConnectionModesEnum%TdsConnectionModes=', TdsConnectionModesEnum%TdsConnectionModes | ||||
#endif | #endif | ||||
call TdsConnectionModesEnum%OnTdsConnectionModesChange%RunAll() | |||||
!**call TdsConnectionModesEnum%OnTdsConnectionModesChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsConnectionModes() | integer function Get_TdsConnectionModes() | ||||
@@ -1,9 +1,9 @@ | |||||
module CTdsElevatorModesEnumVariables | module CTdsElevatorModesEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
type:: TdsElevatorModesEnumType | type:: TdsElevatorModesEnumType | ||||
integer :: TdsElevatorModes = 0 | integer :: TdsElevatorModes = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsElevatorModesChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsElevatorModesChange | |||||
end type TdsElevatorModesEnumType | end type TdsElevatorModesEnumType | ||||
type(TdsElevatorModesEnumType)::TdsElevatorModesEnum | type(TdsElevatorModesEnumType)::TdsElevatorModesEnum | ||||
enum, bind(c) | enum, bind(c) | ||||
@@ -26,7 +26,7 @@ module CTdsElevatorModesEnumVariables | |||||
if(TdsElevatorModesEnum%TdsElevatorModes == v) return | if(TdsElevatorModesEnum%TdsElevatorModes == v) return | ||||
#endif | #endif | ||||
TdsElevatorModesEnum%TdsElevatorModes = v | TdsElevatorModesEnum%TdsElevatorModes = v | ||||
call TdsElevatorModesEnum%OnTdsElevatorModesChange%RunAll() | |||||
!**call TdsElevatorModesEnum%OnTdsElevatorModesChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsElevatorModes() | integer function Get_TdsElevatorModes() | ||||
@@ -268,19 +268,19 @@ module CTongNotification | |||||
end subroutine | end subroutine | ||||
subroutine Subscribe_TongNotification() | |||||
implicit none | |||||
! subroutine Subscribe_TongNotification() | |||||
! implicit none | |||||
call UnitySignals%OnOperationConditionChange%Add(Evaluate_TongNotification) | |||||
call SoftwareInputs%OnHookHeightChange%Add(Evaluate_TongNotification) | |||||
call UnityInputs%OnJointConnectionPossibleChange%Add(Evaluate_TongNotification) | |||||
call UnityInputs%OnSingleSetInMouseHoleChange%Add(Evaluate_TongNotification) | |||||
call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_TongNotification) | |||||
call KellyConnectionEnum%OnKellyConnectionChange%Add(Evaluate_TongNotification) | |||||
call UnitySignals%OnSwingChange%Add(Evaluate_TongNotification) | |||||
call UnitySignals%OnSlipsChange%Add(Evaluate_TongNotification) | |||||
! call UnitySignals%OnOperationConditionChange%Add(Evaluate_TongNotification) | |||||
! ! call softwareInputs%OnHookHeightChange%Add(Evaluate_TongNotification) | |||||
! call UnityInputs%OnJointConnectionPossibleChange%Add(Evaluate_TongNotification) | |||||
! call UnityInputs%OnSingleSetInMouseHoleChange%Add(Evaluate_TongNotification) | |||||
! call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_TongNotification) | |||||
! call KellyConnectionEnum%OnKellyConnectionChange%Add(Evaluate_TongNotification) | |||||
! call UnitySignals%OnSwingChange%Add(Evaluate_TongNotification) | |||||
! call UnitySignals%OnSlipsChange%Add(Evaluate_TongNotification) | |||||
end subroutine | |||||
! end subroutine | |||||
@@ -198,24 +198,19 @@ module CUnlatchLedNotification | |||||
call Set_UnlatchLed(.false.) | call Set_UnlatchLed(.false.) | ||||
endif | endif | ||||
end subroutine | end subroutine | ||||
subroutine Subscribe_UnlatchLed() | |||||
implicit none | |||||
call UnitySignals%OnOperationConditionChange%Add(Evaluate_UnlatchLed) | |||||
call SoftwareInputs%OnHookHeightChange%Add(Evaluate_UnlatchLed) | |||||
call SoftwareInputs%OnStandRackChanged%Add(Evaluate_UnlatchLed) | |||||
call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_UnlatchLed) | |||||
call UnitySignals%OnSwingChange%Add(Evaluate_UnlatchLed) | |||||
call UnitySignals%OnSlipsChange%Add(Evaluate_UnlatchLed) | |||||
call Notifications%OnLatchLedChange%Add(Evaluate_UnlatchLed) | |||||
call Notifications%OnFillMouseHoleLedChange%Add(Evaluate_UnlatchLed) | |||||
end subroutine | |||||
! subroutine Subscribe_UnlatchLed() | |||||
! implicit none | |||||
! !**call UnitySignals%OnOperationConditionChange%Add(Evaluate_UnlatchLed) | |||||
! ! call softwareInputs%OnHookHeightChange%Add(Evaluate_UnlatchLed) | |||||
! ! call softwareInputs%OnStandRackChanged%Add(Evaluate_UnlatchLed) | |||||
! call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_UnlatchLed) | |||||
! !**call UnitySignals%OnSwingChange%Add(Evaluate_UnlatchLed) | |||||
! !**call UnitySignals%OnSlipsChange%Add(Evaluate_UnlatchLed) | |||||
! !**call Notifications%OnLatchLedChange%Add(Evaluate_UnlatchLed) | |||||
! !**call Notifications%OnFillMouseHoleLedChange%Add(Evaluate_UnlatchLed) | |||||
! end subroutine | |||||
end module CUnlatchLedNotification | end module CUnlatchLedNotification |
@@ -1,57 +1,57 @@ | |||||
module NotificationVariables | module NotificationVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
type::NotificationType | type::NotificationType | ||||
logical :: CloseKellyCockLed = .false. | logical :: CloseKellyCockLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnCloseKellyCockLedChange | |||||
! type(VoidEventHandlerCollection) :: OnCloseKellyCockLedChange | |||||
logical :: CloseSafetyValveLed = .false. | logical :: CloseSafetyValveLed = .false. | ||||
integer :: operation_CloseSafetyValveLed = 0 | integer :: operation_CloseSafetyValveLed = 0 | ||||
type(VoidEventHandlerCollection) :: OnCloseSafetyValveLedChange | |||||
! type(VoidEventHandlerCollection) :: OnCloseSafetyValveLedChange | |||||
logical :: FillMouseHoleLed = .false. | logical :: FillMouseHoleLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnFillMouseHoleLedChange | |||||
! type(VoidEventHandlerCollection) :: OnFillMouseHoleLedChange | |||||
logical :: IrIBopLed = .false. | logical :: IrIBopLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnIrIBopLedChange | |||||
! type(VoidEventHandlerCollection) :: OnIrIBopLedChange | |||||
logical :: IrSafetyValveLed = .false. | logical :: IrSafetyValveLed = .false. | ||||
integer :: operation_IrSafetyValveLed = 0 | integer :: operation_IrSafetyValveLed = 0 | ||||
type(VoidEventHandlerCollection) :: OnIrSafetyValveLedChange | |||||
! type(VoidEventHandlerCollection) :: OnIrSafetyValveLedChange | |||||
logical :: LatchLed = .false. | logical :: LatchLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnLatchLedChange | |||||
! type(VoidEventHandlerCollection) :: OnLatchLedChange | |||||
logical :: OpenKellyCockLed = .false. | logical :: OpenKellyCockLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnOpenKellyCockLedChange | |||||
! type(VoidEventHandlerCollection) :: OnOpenKellyCockLedChange | |||||
logical :: OpenSafetyValveLed = .false. | logical :: OpenSafetyValveLed = .false. | ||||
integer :: operation_OpenSafetyValveLed = 0 | integer :: operation_OpenSafetyValveLed = 0 | ||||
type(VoidEventHandlerCollection) :: OnOpenSafetyValveLedChange | |||||
! type(VoidEventHandlerCollection) :: OnOpenSafetyValveLedChange | |||||
logical :: SlipsNotification = .false. | logical :: SlipsNotification = .false. | ||||
! procedure (ActionBool), pointer :: SlipsNotificationPtr | ! procedure (ActionBool), pointer :: SlipsNotificationPtr | ||||
type(VoidEventHandlerCollection) :: OnSlipsNotificationChange | |||||
! type(VoidEventHandlerCollection) :: OnSlipsNotificationChange | |||||
logical :: SwingLed = .false. | logical :: SwingLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnSwingLedChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingLedChange | |||||
logical :: IbopLed = .false. | logical :: IbopLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnIbopLedChange | |||||
! type(VoidEventHandlerCollection) :: OnIbopLedChange | |||||
logical :: PowerLed = .false. | logical :: PowerLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnPowerLedChange | |||||
! type(VoidEventHandlerCollection) :: OnPowerLedChange | |||||
integer :: TorqueWrenchLed = 0 | integer :: TorqueWrenchLed = 0 | ||||
type(VoidEventHandlerCollection) :: OnTorqueWrenchLedChange | |||||
! type(VoidEventHandlerCollection) :: OnTorqueWrenchLedChange | |||||
logical :: TongNotification = .false. | logical :: TongNotification = .false. | ||||
! procedure (ActionBool), pointer :: TongNotificationPtr | ! procedure (ActionBool), pointer :: TongNotificationPtr | ||||
type(VoidEventHandlerCollection) :: OnTongNotificationChange | |||||
! type(VoidEventHandlerCollection) :: OnTongNotificationChange | |||||
logical :: UnlatchLed = .false. | logical :: UnlatchLed = .false. | ||||
type(VoidEventHandlerCollection) :: OnUnlatchLedChange | |||||
! type(VoidEventHandlerCollection) :: OnUnlatchLedChange | |||||
end type NotificationType | end type NotificationType | ||||
type(NotificationType)::notifications | type(NotificationType)::notifications | ||||
@@ -74,7 +74,7 @@ module NotificationVariables | |||||
DrillingConsole%UnlatchPipeLED = 0 | DrillingConsole%UnlatchPipeLED = 0 | ||||
endif | endif | ||||
call notifications%OnUnlatchLedChange%RunAll() | |||||
!**call notifications%OnUnlatchLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_UnlatchLed() | logical function Get_UnlatchLed() | ||||
@@ -89,11 +89,11 @@ module NotificationVariables | |||||
if(notifications%TongNotification == v) return | if(notifications%TongNotification == v) return | ||||
#endif | #endif | ||||
notifications%TongNotification = v | notifications%TongNotification = v | ||||
! if(associated(notifications%TongNotificationPtr)) call notifications%TongNotificationPtr(notifications%TongNotification) | |||||
! if(associated(notifications%TongNotificationPtr)) !**call notifications%TongNotificationPtr(notifications%TongNotification) | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'notifications%TongNotification=', notifications%TongNotification | print*, 'notifications%TongNotification=', notifications%TongNotification | ||||
#endif | #endif | ||||
call notifications%OnTongNotificationChange%RunAll() | |||||
!**call notifications%OnTongNotificationChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_TongNotification() | logical function Get_TongNotification() | ||||
@@ -111,7 +111,7 @@ module NotificationVariables | |||||
#endif | #endif | ||||
notifications%TorqueWrenchLed = v | notifications%TorqueWrenchLed = v | ||||
TopDrivePanel%TopDriveTorqueWrenchLed = v | TopDrivePanel%TopDriveTorqueWrenchLed = v | ||||
call notifications%OnTorqueWrenchLedChange%RunAll() | |||||
!**call notifications%OnTorqueWrenchLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_TorqueWrenchLed() | logical function Get_TorqueWrenchLed() | ||||
@@ -136,7 +136,7 @@ module NotificationVariables | |||||
TopDrivePanel%TopDriveTdsPowerLed = 0 | TopDrivePanel%TopDriveTdsPowerLed = 0 | ||||
endif | endif | ||||
call notifications%OnPowerLedChange%RunAll() | |||||
!**call notifications%OnPowerLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_PowerLed() | logical function Get_PowerLed() | ||||
@@ -163,7 +163,7 @@ module NotificationVariables | |||||
call OpenTopDriveIBop() | call OpenTopDriveIBop() | ||||
endif | endif | ||||
call notifications%OnIbopLedChange%RunAll() | |||||
!**call notifications%OnIbopLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_IbopLed() | logical function Get_IbopLed() | ||||
@@ -185,7 +185,7 @@ module NotificationVariables | |||||
else | else | ||||
DrillingConsole%SwingLed = 0 | DrillingConsole%SwingLed = 0 | ||||
endif | endif | ||||
call notifications%OnSwingLedChange%RunAll() | |||||
!**call notifications%OnSwingLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SwingLed() | logical function Get_SwingLed() | ||||
@@ -200,11 +200,11 @@ module NotificationVariables | |||||
if(notifications%SlipsNotification == v) return | if(notifications%SlipsNotification == v) return | ||||
#endif | #endif | ||||
notifications%SlipsNotification = v | notifications%SlipsNotification = v | ||||
! if(associated(notifications%SlipsNotificationPtr)) call notifications%SlipsNotificationPtr(notifications%SlipsNotification) | |||||
! if(associated(notifications%SlipsNotificationPtr)) !**call notifications%SlipsNotificationPtr(notifications%SlipsNotification) | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'notifications%SlipsNotification=', notifications%SlipsNotification | print*, 'notifications%SlipsNotification=', notifications%SlipsNotification | ||||
#endif | #endif | ||||
call notifications%OnSlipsNotificationChange%RunAll() | |||||
!**call notifications%OnSlipsNotificationChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SlipsNotification() | logical function Get_SlipsNotification() | ||||
@@ -230,7 +230,7 @@ module NotificationVariables | |||||
if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_OpenSafetyValveLed == 1) call OpenSafetyValve_TripMode() | if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_OpenSafetyValveLed == 1) call OpenSafetyValve_TripMode() | ||||
endif | endif | ||||
call notifications%OnOpenSafetyValveLedChange%RunAll() | |||||
!**call notifications%OnOpenSafetyValveLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_OpenSafetyValveLed() | logical function Get_OpenSafetyValveLed() | ||||
@@ -260,7 +260,7 @@ module NotificationVariables | |||||
! OpenKellyCockLedHw = 0 | ! OpenKellyCockLedHw = 0 | ||||
!endif | !endif | ||||
call notifications%OnOpenKellyCockLedChange%RunAll() | |||||
!**call notifications%OnOpenKellyCockLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_OpenKellyCockLed() | logical function Get_OpenKellyCockLed() | ||||
@@ -283,7 +283,7 @@ module NotificationVariables | |||||
else | else | ||||
DrillingConsole%LatchPipeLED = 0 | DrillingConsole%LatchPipeLED = 0 | ||||
endif | endif | ||||
call notifications%OnLatchLedChange%RunAll() | |||||
!**call notifications%OnLatchLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_LatchLed() | logical function Get_LatchLed() | ||||
@@ -327,7 +327,7 @@ module NotificationVariables | |||||
call Set_SafetyValve_Remove() | call Set_SafetyValve_Remove() | ||||
endif | endif | ||||
call notifications%OnIrSafetyValveLedChange%RunAll() | |||||
!**call notifications%OnIrSafetyValveLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_IrSafetyValveLed() | logical function Get_IrSafetyValveLed() | ||||
@@ -354,7 +354,7 @@ module NotificationVariables | |||||
call RemoveIBop() | call RemoveIBop() | ||||
call Set_Ibop_Remove() | call Set_Ibop_Remove() | ||||
endif | endif | ||||
call notifications%OnIrIBopLedChange%RunAll() | |||||
!**call notifications%OnIrIBopLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_IrIBopLed() | logical function Get_IrIBopLed() | ||||
@@ -379,7 +379,7 @@ module NotificationVariables | |||||
DrillingConsole%FillMouseHoleLed = 0 | DrillingConsole%FillMouseHoleLed = 0 | ||||
!call Set_MouseHole(MOUSE_HOLE_EMPTY) | !call Set_MouseHole(MOUSE_HOLE_EMPTY) | ||||
endif | endif | ||||
call notifications%OnFillMouseHoleLedChange%RunAll() | |||||
!**call notifications%OnFillMouseHoleLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_FillMouseHoleLed() | logical function Get_FillMouseHoleLed() | ||||
@@ -399,7 +399,7 @@ module NotificationVariables | |||||
if(notifications%CloseKellyCockLed) then | if(notifications%CloseKellyCockLed) then | ||||
call CloseKellyCock() | call CloseKellyCock() | ||||
endif | endif | ||||
call notifications%OnCloseKellyCockLedChange%RunAll() | |||||
!**call notifications%OnCloseKellyCockLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_CloseKellyCockLed() | logical function Get_CloseKellyCockLed() | ||||
@@ -423,7 +423,7 @@ module NotificationVariables | |||||
if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 0) call CloseSafetyValve_KellyMode() | if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 0) call CloseSafetyValve_KellyMode() | ||||
if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 1) call CloseSafetyValve_TripMode() | if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 1) call CloseSafetyValve_TripMode() | ||||
endif | endif | ||||
call notifications%OnCloseSafetyValveLedChange%RunAll() | |||||
!**call notifications%OnCloseSafetyValveLedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_CloseSafetyValveLed() | logical function Get_CloseSafetyValveLed() | ||||
@@ -1,26 +1,26 @@ | |||||
module PermissionsVariables | module PermissionsVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
type::PermissionsType | type::PermissionsType | ||||
logical :: FillupHeadPermission = .false. | logical :: FillupHeadPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnFillupHeadPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnFillupHeadPermissionChange | |||||
logical :: InstallFillupHeadPermission = .false. | logical :: InstallFillupHeadPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnInstallFillupHeadPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnInstallFillupHeadPermissionChange | |||||
logical :: InstallMudBucketPermission = .false. | logical :: InstallMudBucketPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnInstallMudBucketPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnInstallMudBucketPermissionChange | |||||
logical :: IrIbopPermission = .false. | logical :: IrIbopPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnIrIbopPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnIrIbopPermissionChange | |||||
logical :: IrSafetyValvePermission = .false. | logical :: IrSafetyValvePermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnIrSafetyValvePermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnIrSafetyValvePermissionChange | |||||
logical :: RemoveFillupHeadPermission = .false. | logical :: RemoveFillupHeadPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnRemoveFillupHeadPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnRemoveFillupHeadPermissionChange | |||||
logical :: RemoveMudBucketPermission = .false. | logical :: RemoveMudBucketPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnRemoveMudBucketPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnRemoveMudBucketPermissionChange | |||||
logical :: SwingDrillPermission = .false. | logical :: SwingDrillPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnSwingDrillPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingDrillPermissionChange | |||||
logical :: SwingOffPermission = .false. | logical :: SwingOffPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnSwingOffPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingOffPermissionChange | |||||
logical :: SwingTiltPermission = .false. | logical :: SwingTiltPermission = .false. | ||||
type(VoidEventHandlerCollection) :: OnSwingTiltPermissionChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingTiltPermissionChange | |||||
end type PermissionsType | end type PermissionsType | ||||
type(PermissionsType):: permissions | type(PermissionsType):: permissions | ||||
@@ -37,7 +37,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%SwingTiltPermission=', permissions%SwingTiltPermission | print*, 'permissions%SwingTiltPermission=', permissions%SwingTiltPermission | ||||
#endif | #endif | ||||
call permissions%OnSwingTiltPermissionChange%RunAll() | |||||
!**call permissions%OnSwingTiltPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SwingTiltPermission() | logical function Get_SwingTiltPermission() | ||||
@@ -55,7 +55,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%SwingOffPermission=', permissions%SwingOffPermission | print*, 'permissions%SwingOffPermission=', permissions%SwingOffPermission | ||||
#endif | #endif | ||||
call permissions%OnSwingOffPermissionChange%RunAll() | |||||
!**call permissions%OnSwingOffPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SwingOffPermission() | logical function Get_SwingOffPermission() | ||||
@@ -73,7 +73,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%SwingDrillPermission=', permissions%SwingDrillPermission | print*, 'permissions%SwingDrillPermission=', permissions%SwingDrillPermission | ||||
#endif | #endif | ||||
call permissions%OnSwingDrillPermissionChange%RunAll() | |||||
!**call permissions%OnSwingDrillPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SwingDrillPermission() | logical function Get_SwingDrillPermission() | ||||
@@ -91,7 +91,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%RemoveMudBucketPermission=', permissions%RemoveMudBucketPermission | print*, 'permissions%RemoveMudBucketPermission=', permissions%RemoveMudBucketPermission | ||||
#endif | #endif | ||||
call permissions%OnRemoveMudBucketPermissionChange%RunAll() | |||||
!**call permissions%OnRemoveMudBucketPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_RemoveMudBucketPermission() | logical function Get_RemoveMudBucketPermission() | ||||
@@ -110,7 +110,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%RemoveFillupHeadPermission=', permissions%RemoveFillupHeadPermission | print*, 'permissions%RemoveFillupHeadPermission=', permissions%RemoveFillupHeadPermission | ||||
#endif | #endif | ||||
call permissions%OnRemoveFillupHeadPermissionChange%RunAll() | |||||
!**call permissions%OnRemoveFillupHeadPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_RemoveFillupHeadPermission() | logical function Get_RemoveFillupHeadPermission() | ||||
@@ -128,7 +128,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%IrSafetyValvePermission=', permissions%IrSafetyValvePermission | print*, 'permissions%IrSafetyValvePermission=', permissions%IrSafetyValvePermission | ||||
#endif | #endif | ||||
call permissions%OnIrSafetyValvePermissionChange%RunAll() | |||||
!**call permissions%OnIrSafetyValvePermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_IrSafetyValvePermission() | logical function Get_IrSafetyValvePermission() | ||||
@@ -146,7 +146,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%IrIbopPermission=', permissions%IrIbopPermission | print*, 'permissions%IrIbopPermission=', permissions%IrIbopPermission | ||||
#endif | #endif | ||||
call permissions%OnIrIbopPermissionChange%RunAll() | |||||
!**call permissions%OnIrIbopPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_IrIbopPermission() | logical function Get_IrIbopPermission() | ||||
@@ -165,7 +165,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'permissions%InstallMudBucketPermission=', permissions%InstallMudBucketPermission | print*, 'permissions%InstallMudBucketPermission=', permissions%InstallMudBucketPermission | ||||
#endif | #endif | ||||
call permissions%OnInstallMudBucketPermissionChange%RunAll() | |||||
!**call permissions%OnInstallMudBucketPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_InstallMudBucketPermission() | logical function Get_InstallMudBucketPermission() | ||||
@@ -183,7 +183,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'InstallFillupHeadPermission=', permissions%InstallFillupHeadPermission | print*, 'InstallFillupHeadPermission=', permissions%InstallFillupHeadPermission | ||||
#endif | #endif | ||||
call permissions%OnInstallFillupHeadPermissionChange%RunAll() | |||||
!**call permissions%OnInstallFillupHeadPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_InstallFillupHeadPermission() | logical function Get_InstallFillupHeadPermission() | ||||
@@ -201,7 +201,7 @@ use CVoidEventHandlerCollection | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'FillupHeadPermission=', permissions%FillupHeadPermission | print*, 'FillupHeadPermission=', permissions%FillupHeadPermission | ||||
#endif | #endif | ||||
call permissions%OnFillupHeadPermissionChange%RunAll() | |||||
!**call permissions%OnFillupHeadPermissionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_FillupHeadPermission() | logical function Get_FillupHeadPermission() | ||||
@@ -1,24 +1,24 @@ | |||||
module SoftwareInputsVariables | module SoftwareInputsVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
type:: SoftwareInputsType | type:: SoftwareInputsType | ||||
real :: HookHeight = 0 | real :: HookHeight = 0 | ||||
type(VoidEventHandlerCollection) :: OnHookHeightChange | |||||
! type(VoidEventHandlerCollection) :: OnHookHeightChange | |||||
real :: IbopHeight = 0 | real :: IbopHeight = 0 | ||||
type(VoidEventHandlerCollection) :: OnIbopHeightChange | |||||
! type(VoidEventHandlerCollection) :: OnIbopHeightChange | |||||
real :: NearFloorConnection = 0 | real :: NearFloorConnection = 0 | ||||
type(VoidEventHandlerCollection) :: OnNearFloorConnectionChange | |||||
! type(VoidEventHandlerCollection) :: OnNearFloorConnectionChange | |||||
real :: SafetyValveHeight = 0 | real :: SafetyValveHeight = 0 | ||||
type(VoidEventHandlerCollection) :: OnSafetyValveHeightChange | |||||
! type(VoidEventHandlerCollection) :: OnSafetyValveHeightChange | |||||
logical :: SlackOff = .false. | logical :: SlackOff = .false. | ||||
type(VoidEventHandlerCollection) :: OnSlackOffChange | |||||
! type(VoidEventHandlerCollection) :: OnSlackOffChange | |||||
integer :: StandRack = 0 | integer :: StandRack = 0 | ||||
type(VoidEventHandlerCollection) :: OnStandRackChanged | |||||
! type(VoidEventHandlerCollection) :: OnStandRackChanged | |||||
real :: StringPressure = 0 | real :: StringPressure = 0 | ||||
type(VoidEventHandlerCollection) :: OnStringPressureChange | |||||
! type(VoidEventHandlerCollection) :: OnStringPressureChange | |||||
real :: TdsStemJointHeight = 0 | real :: TdsStemJointHeight = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsStemJointHeightChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsStemJointHeightChange | |||||
logical :: ZeroStringSpeed = .false. | logical :: ZeroStringSpeed = .false. | ||||
type(VoidEventHandlerCollection) :: OnZeroStringSpeedChange | |||||
! type(VoidEventHandlerCollection) :: OnZeroStringSpeedChange | |||||
end type SoftwareInputsType | end type SoftwareInputsType | ||||
type(SoftwareInputsType):: softwareInputs | type(SoftwareInputsType):: softwareInputs | ||||
@@ -34,7 +34,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'ZeroStringSpeed=', softwareInputs%ZeroStringSpeed | print*, 'ZeroStringSpeed=', softwareInputs%ZeroStringSpeed | ||||
#endif | #endif | ||||
call softwareInputs%OnZeroStringSpeedChange%RunAll() | |||||
! call softwareInputs%OnZeroStringSpeedChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_ZeroStringSpeed() | logical function Get_ZeroStringSpeed() | ||||
@@ -53,7 +53,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsStemJointHeight=', softwareInputs%TdsStemJointHeight | print*, 'TdsStemJointHeight=', softwareInputs%TdsStemJointHeight | ||||
#endif | #endif | ||||
call softwareInputs%OnTdsStemJointHeightChange%RunAll() | |||||
! call softwareInputs%OnTdsStemJointHeightChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_TdsStemJointHeight() | real function Get_TdsStemJointHeight() | ||||
@@ -72,7 +72,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'StringPressure=', softwareInputs%StringPressure | print*, 'StringPressure=', softwareInputs%StringPressure | ||||
#endif | #endif | ||||
call softwareInputs%OnStringPressureChange%RunAll() | |||||
! call softwareInputs%OnStringPressureChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_StringPressure() | real function Get_StringPressure() | ||||
@@ -90,7 +90,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'StandRack=', softwareInputs%StandRack | print*, 'StandRack=', softwareInputs%StandRack | ||||
#endif | #endif | ||||
call softwareInputs%OnStandRackChanged%RunAll() | |||||
! call softwareInputs%OnStandRackChanged%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_StandRack() | integer function Get_StandRack() | ||||
@@ -108,7 +108,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'SlackOff=', softwareInputs%SlackOff | print*, 'SlackOff=', softwareInputs%SlackOff | ||||
#endif | #endif | ||||
call softwareInputs%OnSlackOffChange%RunAll() | |||||
! call softwareInputs%OnSlackOffChange%RunAll() | |||||
end subroutine | end subroutine | ||||
logical function Get_SlackOff() | logical function Get_SlackOff() | ||||
@@ -126,7 +126,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'SafetyValveHeight=', softwareInputs%SafetyValveHeight | print*, 'SafetyValveHeight=', softwareInputs%SafetyValveHeight | ||||
#endif | #endif | ||||
call softwareInputs%OnSafetyValveHeightChange%RunAll() | |||||
! call softwareInputs%OnSafetyValveHeightChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_SafetyValveHeight() | real function Get_SafetyValveHeight() | ||||
@@ -146,7 +146,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'NearFloorConnection=', softwareInputs%NearFloorConnection | print*, 'NearFloorConnection=', softwareInputs%NearFloorConnection | ||||
#endif | #endif | ||||
call softwareInputs%OnNearFloorConnectionChange%RunAll() | |||||
! call softwareInputs%OnNearFloorConnectionChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_NearFloorConnection() | real function Get_NearFloorConnection() | ||||
@@ -165,7 +165,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'IbopHeight=', softwareInputs%IbopHeight | print*, 'IbopHeight=', softwareInputs%IbopHeight | ||||
#endif | #endif | ||||
call softwareInputs%OnIbopHeightChange%RunAll() | |||||
! call softwareInputs%OnIbopHeightChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_IbopHeight() | real function Get_IbopHeight() | ||||
@@ -184,7 +184,7 @@ module SoftwareInputsVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'HookHeight=', softwareInputs%HookHeight | print*, 'HookHeight=', softwareInputs%HookHeight | ||||
#endif | #endif | ||||
call softwareInputs%OnHookHeightChange%RunAll() | |||||
! call softwareInputs%OnHookHeightChange%RunAll() | |||||
end subroutine | end subroutine | ||||
real function Get_HookHeight() | real function Get_HookHeight() | ||||
@@ -5,7 +5,7 @@ module CStringUpdateVariables | |||||
public | public | ||||
type(IntegerEventHandlerCollection) :: OnStringUpdateChange | |||||
!**type(IntegerEventHandlerCollection) :: OnStringUpdateChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator STRING_UPDATE_NEUTRAL | enumerator STRING_UPDATE_NEUTRAL | ||||
@@ -1,5 +1,5 @@ | |||||
module CUnityInputs | module CUnityInputs | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
type :: UnityInputsType | type :: UnityInputsType | ||||
logical :: ElevatorConnectionPossible | logical :: ElevatorConnectionPossible | ||||
@@ -22,15 +22,15 @@ module CUnityInputs | |||||
! public | ! public | ||||
type(VoidEventHandlerCollection) :: OnElevatorConnectionPossibleChange | |||||
type(VoidEventHandlerCollection) :: OnJointConnectionPossibleChange | |||||
type(VoidEventHandlerCollection) :: OnIsKellyBushingSetInTableChange | |||||
type(VoidEventHandlerCollection) :: OnElevatorPickupChange | |||||
type(VoidEventHandlerCollection) :: OnNearFloorPositionChange | |||||
type(VoidEventHandlerCollection) :: OnSingleSetInMouseHoleChange | |||||
! type(VoidEventHandlerCollection) :: OnElevatorConnectionPossibleChange | |||||
! type(VoidEventHandlerCollection) :: OnJointConnectionPossibleChange | |||||
! type(VoidEventHandlerCollection) :: OnIsKellyBushingSetInTableChange | |||||
! type(VoidEventHandlerCollection) :: OnElevatorPickupChange | |||||
! type(VoidEventHandlerCollection) :: OnNearFloorPositionChange | |||||
! type(VoidEventHandlerCollection) :: OnSingleSetInMouseHoleChange | |||||
type(VoidEventHandlerCollection) :: OnTdsConnectionPossibleChange | |||||
type(VoidEventHandlerCollection) :: OnTdsStemInChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsConnectionPossibleChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsStemInChange | |||||
end type UnityInputsType | end type UnityInputsType | ||||
type(UnityInputsType)::UnityInputs | type(UnityInputsType)::UnityInputs | ||||
@@ -306,7 +306,7 @@ module CUnityInputs | |||||
! if(UnityInputs%ElevatorConnectionPossible == v) return | ! if(UnityInputs%ElevatorConnectionPossible == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%ElevatorConnectionPossible = v | ! UnityInputs%ElevatorConnectionPossible = v | ||||
! call UnityInputs%OnElevatorConnectionPossibleChange%RunAll() | |||||
! !**call UnityInputs%OnElevatorConnectionPossibleChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'ElevatorConnectionPossible=', UnityInputs%ElevatorConnectionPossible | ! print*, 'ElevatorConnectionPossible=', UnityInputs%ElevatorConnectionPossible | ||||
! #endif | ! #endif | ||||
@@ -341,7 +341,7 @@ module CUnityInputs | |||||
! if(UnityInputs%JointConnectionPossible == v) return | ! if(UnityInputs%JointConnectionPossible == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%JointConnectionPossible = v | ! UnityInputs%JointConnectionPossible = v | ||||
! call UnityInputs%OnJointConnectionPossibleChange%RunAll() | |||||
! !**call UnityInputs%OnJointConnectionPossibleChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'JointConnectionPossible=', UnityInputs%JointConnectionPossible | ! print*, 'JointConnectionPossible=', UnityInputs%JointConnectionPossible | ||||
! #endif | ! #endif | ||||
@@ -373,7 +373,7 @@ module CUnityInputs | |||||
! if(UnityInputs%IsKellyBushingSetInTable == v) return | ! if(UnityInputs%IsKellyBushingSetInTable == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%IsKellyBushingSetInTable = v | ! UnityInputs%IsKellyBushingSetInTable = v | ||||
! call UnityInputs%OnIsKellyBushingSetInTableChange%RunAll() | |||||
! !**call UnityInputs%OnIsKellyBushingSetInTableChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'IsKellyBushingSetInTable=', UnityInputs%IsKellyBushingSetInTable | ! print*, 'IsKellyBushingSetInTable=', UnityInputs%IsKellyBushingSetInTable | ||||
! #endif | ! #endif | ||||
@@ -406,7 +406,7 @@ module CUnityInputs | |||||
! if(UnityInputs%ElevatorPickup == v) return | ! if(UnityInputs%ElevatorPickup == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%ElevatorPickup = v | ! UnityInputs%ElevatorPickup = v | ||||
! call UnityInputs%OnElevatorPickupChange%RunAll() | |||||
! !**call UnityInputs%OnElevatorPickupChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'ElevatorPickup =', UnityInputs%ElevatorPickup | ! print*, 'ElevatorPickup =', UnityInputs%ElevatorPickup | ||||
! #endif | ! #endif | ||||
@@ -438,7 +438,7 @@ module CUnityInputs | |||||
if(UnityInputs%NearFloorPosition == v) return | if(UnityInputs%NearFloorPosition == v) return | ||||
#endif | #endif | ||||
UnityInputs%NearFloorPosition = v | UnityInputs%NearFloorPosition = v | ||||
call UnityInputs%OnNearFloorPositionChange%RunAll() | |||||
!**call UnityInputs%OnNearFloorPositionChange%RunAll() | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'NearFloorPosition =', UnityInputs%NearFloorPosition | print*, 'NearFloorPosition =', UnityInputs%NearFloorPosition | ||||
#endif | #endif | ||||
@@ -482,7 +482,7 @@ module CUnityInputs | |||||
! if(UnityInputs%SingleSetInMouseHole == v) return | ! if(UnityInputs%SingleSetInMouseHole == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%SingleSetInMouseHole = v | ! UnityInputs%SingleSetInMouseHole = v | ||||
! call UnityInputs%OnSingleSetInMouseHoleChange%RunAll() | |||||
! !**call UnityInputs%OnSingleSetInMouseHoleChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'singleSetInMouseHole=', UnityInputs%SingleSetInMouseHole | ! print*, 'singleSetInMouseHole=', UnityInputs%SingleSetInMouseHole | ||||
! #endif | ! #endif | ||||
@@ -551,7 +551,7 @@ module CUnityInputs | |||||
! if(UnityInputs%TdsConnectionPossible == v) return | ! if(UnityInputs%TdsConnectionPossible == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%TdsConnectionPossible = v | ! UnityInputs%TdsConnectionPossible = v | ||||
! call UnityInputs%OnTdsConnectionPossibleChange%RunAll() | |||||
! !**call UnityInputs%OnTdsConnectionPossibleChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'TdsConnectionPossible=', UnityInputs%TdsConnectionPossible | ! print*, 'TdsConnectionPossible=', UnityInputs%TdsConnectionPossible | ||||
! #endif | ! #endif | ||||
@@ -581,7 +581,7 @@ module CUnityInputs | |||||
! if(UnityInputs%TdsStemIn == v) return | ! if(UnityInputs%TdsStemIn == v) return | ||||
! #endif | ! #endif | ||||
! UnityInputs%TdsStemIn = v | ! UnityInputs%TdsStemIn = v | ||||
! call UnityInputs%OnTdsStemInChange%RunAll() | |||||
! !**call UnityInputs%OnTdsStemInChange%RunAll() | |||||
! #ifdef deb | ! #ifdef deb | ||||
! print*, 'TdsStemIn=', UnityInputs%TdsStemIn | ! print*, 'TdsStemIn=', UnityInputs%TdsStemIn | ||||
! #endif | ! #endif | ||||
@@ -22,7 +22,7 @@ module CUnityOutputs | |||||
use CDataDisplayConsoleVariables | use CDataDisplayConsoleVariables | ||||
implicit none | implicit none | ||||
PumpsSpmChanges => Calc_KellyHoseVibrationRate | PumpsSpmChanges => Calc_KellyHoseVibrationRate | ||||
call DataDisplayConsole%OnRotaryRpmChange%Add(Set_RotaryRpm) | |||||
! call DataDisplayConsole%OnRotaryRpmChange%Add(Set_RotaryRpm) | |||||
end subroutine | end subroutine | ||||
@@ -1,11 +1,11 @@ | |||||
module CBucketEnumVariables | module CBucketEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: MudBucket = 0 | integer :: MudBucket = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnMudBucketChange | |||||
! type(VoidEventHandlerCollection) :: OnMudBucketChange | |||||
enum, bind(c) | enum, bind(c) | ||||
!enumerator MUD_BUCKET_NEUTRAL | !enumerator MUD_BUCKET_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CElevatorEnumVariables | module CElevatorEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: Elevator = 0 | integer :: Elevator = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnElevatorChange | |||||
! type(VoidEventHandlerCollection) :: OnElevatorChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator ELEVATOR_NEUTRAL | enumerator ELEVATOR_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CFlowKellyDisconnectEnumVariables | module CFlowKellyDisconnectEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
! integer :: FlowKellyDisconnect = 0 | ! integer :: FlowKellyDisconnect = 0 | ||||
! | ! | ||||
! public | ! public | ||||
! | ! | ||||
! type(VoidEventHandlerCollection) :: OnFlowKellyDisconnectChange | |||||
! ! type(VoidEventHandlerCollection) :: OnFlowKellyDisconnectChange | |||||
! | ! | ||||
! enum, bind(c) | ! enum, bind(c) | ||||
! enumerator FLOW_KELLY_DISCONNECT_NEUTRAL | ! enumerator FLOW_KELLY_DISCONNECT_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CFlowPipeDisconnectEnumVariables | module CFlowPipeDisconnectEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
! integer :: FlowPipeDisconnect = 0 | ! integer :: FlowPipeDisconnect = 0 | ||||
! | ! | ||||
! public | ! public | ||||
! | ! | ||||
! type(VoidEventHandlerCollection) :: OnFlowPipeDisconnectChange | |||||
! ! type(VoidEventHandlerCollection) :: OnFlowPipeDisconnectChange | |||||
! | ! | ||||
! enum, bind(c) | ! enum, bind(c) | ||||
! enumerator FLOW_PIPE_DISCONNECT_NEUTRAL | ! enumerator FLOW_PIPE_DISCONNECT_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CHeadEnumVariables | module CHeadEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: FillupHead = 0 | integer :: FillupHead = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnFillupHeadChange | |||||
! type(VoidEventHandlerCollection) :: OnFillupHeadChange | |||||
enum, bind(c) | enum, bind(c) | ||||
!enumerator FILLUP_HEAD_NEUTRAL | !enumerator FILLUP_HEAD_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CIbopEnumVariables | module CIbopEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: Ibop = 0 | integer :: Ibop = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnIbopChange | |||||
! type(VoidEventHandlerCollection) :: OnIbopChange | |||||
enum, bind(c) | enum, bind(c) | ||||
!enumerator IBOP_NEUTRAL | !enumerator IBOP_NEUTRAL | ||||
@@ -1,12 +1,12 @@ | |||||
module CKellyEnumVariables | module CKellyEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: Kelly = 0 | integer :: Kelly = 0 | ||||
integer :: Kelly_S = 0 | integer :: Kelly_S = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnKellyChange | |||||
! type(VoidEventHandlerCollection) :: OnKellyChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator KELLY_NEUTRAL | enumerator KELLY_NEUTRAL | ||||
@@ -1,12 +1,12 @@ | |||||
module CMouseHoleEnumVariables | module CMouseHoleEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: MouseHole = 0 | integer :: MouseHole = 0 | ||||
integer :: MouseHole_S = 0 | integer :: MouseHole_S = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnMouseHoleChange | |||||
! type(VoidEventHandlerCollection) :: OnMouseHoleChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator MOUSE_HOLE_NEUTRAL | enumerator MOUSE_HOLE_NEUTRAL | ||||
@@ -1,13 +1,13 @@ | |||||
module COperationConditionEnumVariables | module COperationConditionEnumVariables | ||||
use CIntegerEventHandlerCollection | use CIntegerEventHandlerCollection | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: OperationCondition = 0 | integer :: OperationCondition = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnOperationConditionChange | |||||
type(IntegerEventHandlerCollection) :: OnOperationConditionChangeInt | |||||
! type(VoidEventHandlerCollection) :: OnOperationConditionChange | |||||
!**type(IntegerEventHandlerCollection) :: OnOperationConditionChangeInt | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator OPERATION_DRILL | enumerator OPERATION_DRILL | ||||
@@ -1,12 +1,12 @@ | |||||
module CSafetyValveEnumVariables | module CSafetyValveEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: SafetyValve = 0 | integer :: SafetyValve = 0 | ||||
integer :: operation = 0 | integer :: operation = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnSafetyValveChange | |||||
! type(VoidEventHandlerCollection) :: OnSafetyValveChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator SAFETY_VALVE_NEUTRAL | enumerator SAFETY_VALVE_NEUTRAL | ||||
@@ -1,12 +1,12 @@ | |||||
module CSlipsEnumVariables | module CSlipsEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: Slips = 0 | integer :: Slips = 0 | ||||
integer :: Slips_S = 0 | integer :: Slips_S = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnSlipsChange | |||||
! type(VoidEventHandlerCollection) :: OnSlipsChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator SLIPS_NEUTRAL | enumerator SLIPS_NEUTRAL | ||||
@@ -1,5 +1,5 @@ | |||||
module CSwingEnumVariables | module CSwingEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
use CLog4 | use CLog4 | ||||
implicit none | implicit none | ||||
integer :: Swing = 0 | integer :: Swing = 0 | ||||
@@ -7,7 +7,7 @@ module CSwingEnumVariables | |||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnSwingChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator SWING_NEUTRAL | enumerator SWING_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CTdsBackupClampVariables | module CTdsBackupClampVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: TdsBackupClamp = 0 | integer :: TdsBackupClamp = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnTdsBackupClampChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsBackupClampChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator BACKUP_CLAMP_OFF_END | enumerator BACKUP_CLAMP_OFF_END | ||||
@@ -1,12 +1,12 @@ | |||||
module CTdsSpineEnumVariables | module CTdsSpineEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
use CLog4 | use CLog4 | ||||
implicit none | implicit none | ||||
integer :: TdsSpine = 0 | integer :: TdsSpine = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnTdsSpineChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsSpineChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator TDS_SPINE_NEUTRAL | enumerator TDS_SPINE_NEUTRAL | ||||
@@ -1,12 +1,12 @@ | |||||
module CTdsSwingEnumVariables | module CTdsSwingEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
use CLog4 | use CLog4 | ||||
implicit none | implicit none | ||||
integer :: TdsSwing = 0 | integer :: TdsSwing = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnTdsSwingChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsSwingChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator TDS_SWING_NEUTRAL | enumerator TDS_SWING_NEUTRAL | ||||
@@ -1,11 +1,11 @@ | |||||
module CTdsTongEnumVariables | module CTdsTongEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
integer :: TdsTong = 0 | integer :: TdsTong = 0 | ||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnTdsTongChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsTongChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator TDS_TONG_BREAKOUT_END | enumerator TDS_TONG_BREAKOUT_END | ||||
@@ -1,5 +1,5 @@ | |||||
module CTongEnumVariables | module CTongEnumVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
use CLog4 | use CLog4 | ||||
implicit none | implicit none | ||||
integer :: Tong = 0 | integer :: Tong = 0 | ||||
@@ -7,7 +7,7 @@ module CTongEnumVariables | |||||
public | public | ||||
type(VoidEventHandlerCollection) :: OnTongChange | |||||
! type(VoidEventHandlerCollection) :: OnTongChange | |||||
enum, bind(c) | enum, bind(c) | ||||
enumerator TONG_NEUTRAL | enumerator TONG_NEUTRAL | ||||
@@ -1,43 +1,43 @@ | |||||
module UnitySignalVariables | module UnitySignalVariables | ||||
use CVoidEventHandlerCollection | |||||
use CIntegerEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
! use CIntegerEventHandlerCollection | |||||
type:: UnitySignalsType | type:: UnitySignalsType | ||||
integer :: MudBucket = 0 | integer :: MudBucket = 0 | ||||
type(VoidEventHandlerCollection) :: OnMudBucketChange | |||||
! type(VoidEventHandlerCollection) :: OnMudBucketChange | |||||
integer :: Elevator = 0 | integer :: Elevator = 0 | ||||
type(VoidEventHandlerCollection) :: OnElevatorChange | |||||
! type(VoidEventHandlerCollection) :: OnElevatorChange | |||||
integer :: FillupHead = 0 | integer :: FillupHead = 0 | ||||
type(VoidEventHandlerCollection) :: OnFillupHeadChange | |||||
! type(VoidEventHandlerCollection) :: OnFillupHeadChange | |||||
integer :: Ibop = 0 | integer :: Ibop = 0 | ||||
type(VoidEventHandlerCollection) :: OnIbopChange | |||||
! type(VoidEventHandlerCollection) :: OnIbopChange | |||||
integer :: Kelly = 0 | integer :: Kelly = 0 | ||||
type(VoidEventHandlerCollection) :: OnKellyChange | |||||
! type(VoidEventHandlerCollection) :: OnKellyChange | |||||
integer :: MouseHole = 0 | integer :: MouseHole = 0 | ||||
type(VoidEventHandlerCollection) :: OnMouseHoleChange | |||||
! type(VoidEventHandlerCollection) :: OnMouseHoleChange | |||||
integer :: OperationCondition = 0 | integer :: OperationCondition = 0 | ||||
type(VoidEventHandlerCollection) :: OnOperationConditionChange | |||||
type(IntegerEventHandlerCollection) :: OnOperationConditionChangeInt | |||||
! type(VoidEventHandlerCollection) :: OnOperationConditionChange | |||||
! !**type(IntegerEventHandlerCollection) :: OnOperationConditionChangeInt | |||||
integer :: SafetyValve = 0 | integer :: SafetyValve = 0 | ||||
type(VoidEventHandlerCollection) :: OnSafetyValveChange | |||||
! type(VoidEventHandlerCollection) :: OnSafetyValveChange | |||||
integer :: operation = 0 | integer :: operation = 0 | ||||
integer :: Slips = 0 | integer :: Slips = 0 | ||||
integer :: Slips_S = 0 | integer :: Slips_S = 0 | ||||
type(VoidEventHandlerCollection) :: OnSlipsChange | |||||
! type(VoidEventHandlerCollection) :: OnSlipsChange | |||||
integer :: Swing = 0 | integer :: Swing = 0 | ||||
integer :: Swing_S = 0 | integer :: Swing_S = 0 | ||||
type(VoidEventHandlerCollection) :: OnSwingChange | |||||
! type(VoidEventHandlerCollection) :: OnSwingChange | |||||
integer :: TdsBackupClamp = 0 | integer :: TdsBackupClamp = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsBackupClampChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsBackupClampChange | |||||
integer :: TdsSpine = 0 | integer :: TdsSpine = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsSpineChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsSpineChange | |||||
integer :: TdsSwing = 0 | integer :: TdsSwing = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsSwingChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsSwingChange | |||||
integer :: TdsTong = 0 | integer :: TdsTong = 0 | ||||
type(VoidEventHandlerCollection) :: OnTdsTongChange | |||||
! type(VoidEventHandlerCollection) :: OnTdsTongChange | |||||
integer :: Tong = 0 | integer :: Tong = 0 | ||||
integer :: Tong_S = 0 | integer :: Tong_S = 0 | ||||
type(VoidEventHandlerCollection) :: OnTongChange | |||||
! type(VoidEventHandlerCollection) :: OnTongChange | |||||
end type UnitySignalsType | end type UnitySignalsType | ||||
type(UnitySignalsType):: unitySignals | type(UnitySignalsType):: unitySignals | ||||
@@ -160,7 +160,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Tong=', UnitySignals%Tong | print*, 'Tong=', UnitySignals%Tong | ||||
#endif | #endif | ||||
call UnitySignals%OnTongChange%RunAll() | |||||
!**call UnitySignals%OnTongChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Tong() | integer function Get_Tong() | ||||
@@ -179,7 +179,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsTong=', UnitySignals%TdsTong | print*, 'TdsTong=', UnitySignals%TdsTong | ||||
#endif | #endif | ||||
call UnitySignals%OnTdsTongChange%RunAll() | |||||
!**call UnitySignals%OnTdsTongChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsTong() | integer function Get_TdsTong() | ||||
@@ -198,7 +198,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsSwing=', UnitySignals%TdsSwing | print*, 'TdsSwing=', UnitySignals%TdsSwing | ||||
#endif | #endif | ||||
call UnitySignals%OnTdsSwingChange%RunAll() | |||||
!**call UnitySignals%OnTdsSwingChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsSwing() | integer function Get_TdsSwing() | ||||
@@ -217,7 +217,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsSpine=', UnitySignals%TdsSpine | print*, 'TdsSpine=', UnitySignals%TdsSpine | ||||
#endif | #endif | ||||
call UnitySignals%OnTdsSpineChange%RunAll() | |||||
!**call UnitySignals%OnTdsSpineChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsSpine() | integer function Get_TdsSpine() | ||||
@@ -236,7 +236,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'TdsBackupClamp=', UnitySignals%TdsBackupClamp | print*, 'TdsBackupClamp=', UnitySignals%TdsBackupClamp | ||||
#endif | #endif | ||||
call UnitySignals%OnTdsBackupClampChange%RunAll() | |||||
!**call UnitySignals%OnTdsBackupClampChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_TdsBackupClamp() | integer function Get_TdsBackupClamp() | ||||
@@ -255,7 +255,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Swing=', UnitySignals%Swing | print*, 'Swing=', UnitySignals%Swing | ||||
#endif | #endif | ||||
call UnitySignals%OnSwingChange%RunAll() | |||||
!**call UnitySignals%OnSwingChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Swing() | integer function Get_Swing() | ||||
@@ -274,7 +274,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Slips=', UnitySignals%Slips | print*, 'Slips=', UnitySignals%Slips | ||||
#endif | #endif | ||||
call UnitySignals%OnSlipsChange%RunAll() | |||||
!**call UnitySignals%OnSlipsChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Slips() | integer function Get_Slips() | ||||
@@ -304,7 +304,7 @@ module UnitySignalVariables | |||||
print*, 'SafetyValve=SAFETY_VALVE_REMOVE' | print*, 'SafetyValve=SAFETY_VALVE_REMOVE' | ||||
endif | endif | ||||
#endif | #endif | ||||
call UnitySignals%OnSafetyValveChange%RunAll() | |||||
!**call UnitySignals%OnSafetyValveChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_SafetyValve() | integer function Get_SafetyValve() | ||||
@@ -334,8 +334,8 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'OperationCondition=', UnitySignals%OperationCondition | print*, 'OperationCondition=', UnitySignals%OperationCondition | ||||
#endif | #endif | ||||
call UnitySignals%OnOperationConditionChange%RunAll() | |||||
call UnitySignals%OnOperationConditionChangeInt%RunAll(UnitySignals%OperationCondition) | |||||
!**call UnitySignals%OnOperationConditionChange%RunAll() | |||||
!**call UnitySignals%OnOperationConditionChangeInt%RunAll(UnitySignals%OperationCondition) | |||||
end subroutine | end subroutine | ||||
integer function Get_OperationCondition() | integer function Get_OperationCondition() | ||||
@@ -355,7 +355,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'MouseHole=', UnitySignals%MouseHole | print*, 'MouseHole=', UnitySignals%MouseHole | ||||
#endif | #endif | ||||
call UnitySignals%OnMouseHoleChange%RunAll() | |||||
!**call UnitySignals%OnMouseHoleChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_MouseHole() | integer function Get_MouseHole() | ||||
@@ -375,7 +375,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Kelly=', UnitySignals%Kelly | print*, 'Kelly=', UnitySignals%Kelly | ||||
#endif | #endif | ||||
call UnitySignals%OnKellyChange%RunAll() | |||||
!**call UnitySignals%OnKellyChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Kelly() | integer function Get_Kelly() | ||||
@@ -394,7 +394,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Ibop=', UnitySignals%Ibop | print*, 'Ibop=', UnitySignals%Ibop | ||||
#endif | #endif | ||||
call UnitySignals%OnIbopChange%RunAll() | |||||
!**call UnitySignals%OnIbopChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Ibop() | integer function Get_Ibop() | ||||
@@ -421,7 +421,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'FillupHead=', UnitySignals%FillupHead | print*, 'FillupHead=', UnitySignals%FillupHead | ||||
#endif | #endif | ||||
call UnitySignals%OnFillupHeadChange%RunAll() | |||||
!**call UnitySignals%OnFillupHeadChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_FillupHead() | integer function Get_FillupHead() | ||||
@@ -440,7 +440,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'Elevator=', UnitySignals%Elevator | print*, 'Elevator=', UnitySignals%Elevator | ||||
#endif | #endif | ||||
call UnitySignals%OnElevatorChange%RunAll() | |||||
!**call UnitySignals%OnElevatorChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_Elevator() | integer function Get_Elevator() | ||||
@@ -466,7 +466,7 @@ module UnitySignalVariables | |||||
#ifdef deb | #ifdef deb | ||||
print*, 'MudBucket=', UnitySignals%MudBucket | print*, 'MudBucket=', UnitySignals%MudBucket | ||||
#endif | #endif | ||||
call UnitySignals%OnMudBucketChange%RunAll() | |||||
!**call UnitySignals%OnMudBucketChange%RunAll() | |||||
end subroutine | end subroutine | ||||
integer function Get_MudBucket() | integer function Get_MudBucket() | ||||
@@ -54,21 +54,21 @@ module CBitProblemsVariables | |||||
end subroutine | end subroutine | ||||
subroutine ChangePlugJets(status) | subroutine ChangePlugJets(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(BitProblems%PlugJetsPtr)) call BitProblems%PlugJetsPtr(status) | ! if(associated(BitProblems%PlugJetsPtr)) call BitProblems%PlugJetsPtr(status) | ||||
if(status == Clear_StatusType) BitJetsPlugged = 0 | |||||
if(status == Executed_StatusType) BitJetsPlugged = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%BitJetsPlugged = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%BitJetsPlugged = 1 | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeJetWashout(status) | subroutine ChangeJetWashout(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(BitProblems%JetWashoutPtr)) call BitProblems%JetWashoutPtr(status) | ! if(associated(BitProblems%JetWashoutPtr)) call BitProblems%JetWashoutPtr(status) | ||||
if(status == Clear_StatusType) BitJetsWashedOut = 0 | |||||
if(status == Executed_StatusType) BitJetsWashedOut = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%BitJetsWashedOut = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%BitJetsWashedOut = 1 | |||||
endsubroutine | endsubroutine | ||||
@@ -179,12 +179,12 @@ module CChokeProblemsVariables | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke1Plugged(status) | subroutine ChangeManualChoke1Plugged(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(ManualChoke1PluggedPtr)) call ManualChoke1PluggedPtr(status) | ! if(associated(ManualChoke1PluggedPtr)) call ManualChoke1PluggedPtr(status) | ||||
if(status == Clear_StatusType) ManChoke1Plug = 0 | |||||
if(status == Executed_StatusType) ManChoke1Plug = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%ManChoke1Plug = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%ManChoke1Plug = 1 | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke1Fail(status) | subroutine ChangeManualChoke1Fail(status) | ||||
@@ -196,25 +196,25 @@ module CChokeProblemsVariables | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke1Washout(status) | subroutine ChangeManualChoke1Washout(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
use CChokeManifoldVariables | use CChokeManifoldVariables | ||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(ManualChoke1WashoutPtr)) call ManualChoke1WashoutPtr(status) | ! if(associated(ManualChoke1WashoutPtr)) call ManualChoke1WashoutPtr(status) | ||||
if(status == Clear_StatusType) ManChoke1Washout = 0 | |||||
if(status == Executed_StatusType) ManChoke1Washout = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%ManChoke1Washout = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%ManChoke1Washout = 1 | |||||
if(status == Clear_StatusType) ChokeManifold%LeftManChokeOnProblem = .false. | if(status == Clear_StatusType) ChokeManifold%LeftManChokeOnProblem = .false. | ||||
if(status == Executed_StatusType) ChokeManifold%LeftManChokeOnProblem = .true. | if(status == Executed_StatusType) ChokeManifold%LeftManChokeOnProblem = .true. | ||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke2Plugged(status) | subroutine ChangeManualChoke2Plugged(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(ManualChoke2PluggedPtr)) call ManualChoke2PluggedPtr(status) | ! if(associated(ManualChoke2PluggedPtr)) call ManualChoke2PluggedPtr(status) | ||||
if(status == Clear_StatusType) ManChoke2Plug = 0 | |||||
if(status == Executed_StatusType) ManChoke2Plug = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%ManChoke2Plug = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%ManChoke2Plug = 1 | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke2Fail(status) | subroutine ChangeManualChoke2Fail(status) | ||||
@@ -226,13 +226,13 @@ module CChokeProblemsVariables | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeManualChoke2Washout(status) | subroutine ChangeManualChoke2Washout(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
use CChokeManifoldVariables | use CChokeManifoldVariables | ||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(ManualChoke2WashoutPtr)) call ManualChoke2WashoutPtr(status) | ! if(associated(ManualChoke2WashoutPtr)) call ManualChoke2WashoutPtr(status) | ||||
if(status == Clear_StatusType) ManChoke2Washout = 0 | |||||
if(status == Executed_StatusType) ManChoke2Washout = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%ManChoke2Washout = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%ManChoke2Washout = 1 | |||||
if(status == Clear_StatusType) ChokeManifold%RightManChokeOnProblem = .false. | if(status == Clear_StatusType) ChokeManifold%RightManChokeOnProblem = .false. | ||||
if(status == Executed_StatusType) ChokeManifold%RightManChokeOnProblem = .true. | if(status == Executed_StatusType) ChokeManifold%RightManChokeOnProblem = .true. | ||||
@@ -215,12 +215,12 @@ module CGaugesProblemsVariables | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeCasingPressure(status) | subroutine ChangeCasingPressure(status) | ||||
USE FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(CasingPressurePtr)) call CasingPressurePtr(status) | ! if(associated(CasingPressurePtr)) call CasingPressurePtr(status) | ||||
if(status == Clear_StatusType) CasingPressure_DataDisplayMalF = 0 | |||||
if(status == Executed_StatusType) CasingPressure_DataDisplayMalF = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%CasingPressure_DataDisplayMalF = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%CasingPressure_DataDisplayMalF = 1 | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangePump1Strokes(status) | subroutine ChangePump1Strokes(status) | ||||
@@ -373,12 +373,12 @@ module CGaugesProblemsVariables | |||||
endsubroutine | endsubroutine | ||||
subroutine ChangeCasingPressure2(status) | subroutine ChangeCasingPressure2(status) | ||||
use FricPressDropVars | |||||
USE FricPressDropVarsModule | |||||
implicit none | implicit none | ||||
integer, intent (in) :: status | integer, intent (in) :: status | ||||
! if(associated(CasingPressure2Ptr)) call CasingPressure2Ptr(status) | ! if(associated(CasingPressure2Ptr)) call CasingPressure2Ptr(status) | ||||
if(status == Clear_StatusType) CasingPressure_ChokeMalF = 0 | |||||
if(status == Executed_StatusType) CasingPressure_ChokeMalF = 1 | |||||
if(status == Clear_StatusType) FricPressDropVars%CasingPressure_ChokeMalF = 0 | |||||
if(status == Executed_StatusType) FricPressDropVars%CasingPressure_ChokeMalF = 1 | |||||
endsubroutine | endsubroutine | ||||
@@ -1,5 +1,5 @@ | |||||
module CStudentStationVariables | module CStudentStationVariables | ||||
use CVoidEventHandlerCollection | |||||
! use CVoidEventHandlerCollection | |||||
implicit none | implicit none | ||||
public | public | ||||
@@ -11,12 +11,12 @@ module CStudentStationVariables | |||||
logical :: TapSelector | logical :: TapSelector | ||||
end type StudentStationType | end type StudentStationType | ||||
type(StudentStationType)::StudentStation | type(StudentStationType)::StudentStation | ||||
! type(VoidEventHandlerCollection) :: OnStudentStation%FillupHeadInstallationPress | |||||
! type(VoidEventHandlerCollection) :: OnFillupHeadRemovePress | |||||
! ! type(VoidEventHandlerCollection) :: OnStudentStation%FillupHeadInstallationPress | |||||
! ! type(VoidEventHandlerCollection) :: OnFillupHeadRemovePress | |||||
! type(VoidEventHandlerCollection) :: OnMudBoxInstallationPress | |||||
! type(VoidEventHandlerCollection) :: | |||||
! ! type(VoidEventHandlerCollection) :: OnMudBoxInstallationPress | |||||
! ! type(VoidEventHandlerCollection) :: | |||||
@@ -1,7 +1,7 @@ | |||||
SUBROUTINE ANNULAR_SUB1 | SUBROUTINE ANNULAR_SUB1 | ||||
USE VARIABLES | USE VARIABLES | ||||
USE CBopControlPanelVariables | USE CBopControlPanelVariables | ||||
USE PressureDisplayVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
USE CEquipmentsConstants | USE CEquipmentsConstants | ||||
USE CBopStackVariables | USE CBopStackVariables | ||||
@@ -125,7 +125,7 @@ SUBROUTINE ANNULAR_SUB1 | |||||
if (RAM(1)%FourwayValve == 1 .and. Annular%Pannular_reg>AnnularComputational%AnnularMovingPressure .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure & | if (RAM(1)%FourwayValve == 1 .and. Annular%Pannular_reg>AnnularComputational%AnnularMovingPressure .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure & | ||||
.and. (Annular%Annular_closed==0 .or. (Annular%Annular_closed==1 .and.PressureGauges(2) <=100.0) .or. (Annular%Annular_closed==1 .and.PressureGauges(2)>100.0 .and. Annular%Pannular_reg>=AnnularComputational%AnnularSealingPressure))) then ! 1: Open , 0: Close | |||||
.and. (Annular%Annular_closed==0 .or. (Annular%Annular_closed==1 .and. PressureDisplayVARIABLES%PressureGauges(2) <=100.0) .or. (Annular%Annular_closed==1 .and. PressureDisplayVARIABLES%PressureGauges(2)>100.0 .and. Annular%Pannular_reg>=AnnularComputational%AnnularSealingPressure))) then ! 1: Open , 0: Close | |||||
!write(*,*) 'open 2' | !write(*,*) 'open 2' | ||||
RAM(1)%FourwayValve = 0 | RAM(1)%FourwayValve = 0 | ||||
@@ -196,7 +196,7 @@ end if | |||||
SUBROUTINE ANNULAR_SUB2 | SUBROUTINE ANNULAR_SUB2 | ||||
USE VARIABLES | USE VARIABLES | ||||
USE PressureDisplayVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
USE CBopControlPanelVariables | USE CBopControlPanelVariables | ||||
USE CEquipmentsConstants | USE CEquipmentsConstants | ||||
USE CBopStackVariables | USE CBopStackVariables | ||||
@@ -314,7 +314,7 @@ SUBROUTINE ANNULAR_SUB2 | |||||
if (RAM(1)%FourwayValve == 1 .and. Annular%Pannular_reg>AnnularComputational%AnnularMovingPressure & | if (RAM(1)%FourwayValve == 1 .and. Annular%Pannular_reg>AnnularComputational%AnnularMovingPressure & | ||||
.and. (Annular%Annular_closed==0 .or. (Annular%Annular_closed==1 .and.PressureGauges(2) <=100.0) .or. (Annular%Annular_closed==1 .and.PressureGauges(2)>100.0 .and. Annular%Pannular_reg>=AnnularComputational%AnnularSealingPressure))) then | |||||
.and. (Annular%Annular_closed==0 .or. (Annular%Annular_closed==1 .and. PressureDisplayVARIABLES%PressureGauges(2) <=100.0) .or. (Annular%Annular_closed==1 .and. PressureDisplayVARIABLES%PressureGauges(2)>100.0 .and. Annular%Pannular_reg>=AnnularComputational%AnnularSealingPressure))) then | |||||
!write(*,*) 'open 4' | !write(*,*) 'open 4' | ||||
RAM(1)%FourwayValve = 0 | RAM(1)%FourwayValve = 0 | ||||
@@ -123,15 +123,4 @@ AirPumpLine%alpha_Pdownstrem=AirPumpLine%Pdownstrem | |||||
AirPumpLine%alpha_diffpair=0 | AirPumpLine%alpha_diffpair=0 | ||||
AirPumpLine%alpha_lossesair=0 | AirPumpLine%alpha_lossesair=0 | ||||
end | end |
@@ -0,0 +1,148 @@ | |||||
subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | |||||
USE TD_DrillStemComponents | |||||
Use CUnityInputs | |||||
Use CUnityOutputs | |||||
USE CKellyConnectionEnumVariables | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | |||||
use PressureDisplayVARIABLESModule | |||||
implicit none | |||||
Integer i,KickNumber | |||||
!NewInfluxNumber = NoGasPocket | |||||
MudSystem%Flow_timeCounter= MudSystem%Flow_timeCounter+1 | |||||
!if (ChokePanelStrokeResetSwitch == 1) then | |||||
! Flow_timeCounter= 0 | |||||
!endif | |||||
!write(*,*) 'Flow_timeCounter' , Flow_timeCounter | |||||
!===========================Shoe Lost=============================== | |||||
call ShoeLostSub | |||||
!=================================================================== | |||||
MudSystem%iLoc= 1 ! will be changed in KickFlux and Migration or Pump and TripIn (save OP Mud data) | |||||
!KickMigration_2SideBit= .false. | |||||
Call Set_FlowPipeDisconnect(.false.) | |||||
Call Set_FlowKellyDisconnect(.false.) | |||||
call ElementsCreation | |||||
if (MUD(8)%Q > 0.0) call FillingWell_By_BellNipple ! Filling Well Through BellNipple ( Path j11 ) | |||||
!if (MUD(10)%Q > 0.0) call FillingWell_By_Pumps ! Filling Well Through Pumps ( Path j19 ) | |||||
!write(*,*) 'TD_RemoveVolume,Get_JointConnectionPossible=' , TD_RemoveVolume,Get_JointConnectionPossible() | |||||
if (TD_Vol%RemoveVolume > 0.) call DisconnectingPipe !! .and. Get_JointConnectionPossible() == .false.) call DisconnectingPipe | |||||
IF (KickFlux .AND. NOT(KickOffBottom)) THEN | |||||
call Kick_Influx | |||||
endif | |||||
IF ( MudSystem%NewInfluxNumber > 0 ) THEN | |||||
!write(*,*) 'KickOffBottom , ROP=' , KickOffBottom , ROP_Bit%RateOfPenetration | |||||
call Kick_Migration | |||||
endif | |||||
! ============================ must be after migration ============================== | |||||
DO KickNumber= MudSystem%NewInfluxNumber-NoGasPocket+1 , MudSystem%NewInfluxNumber | |||||
! FINDING NEW KICK LOCATIONS: | |||||
MudSystem%Ann_KickLoc= 0 | |||||
MudSystem%Op_KickLoc= 0 | |||||
MudSystem%ChokeLine_KickLoc= 0 | |||||
do i = 1, MudSystem%Ann_MudOrKick%Length () | |||||
if (MudSystem%Ann_MudOrKick%Array(i) == KickNumber) then | |||||
MudSystem%Ann_KickLoc = i | |||||
exit | |||||
endif | |||||
end do | |||||
do i = 1, MudSystem%Op_MudOrKick%Length () | |||||
if (MudSystem%Op_MudOrKick%Array(i) == KickNumber) then | |||||
MudSystem%Op_KickLoc = i | |||||
exit | |||||
endif | |||||
end do | |||||
do i = 1, MudSystem%ChokeLine_MudOrKick%Length () | |||||
if (MudSystem%ChokeLine_MudOrKick%Array(i) == KickNumber) then | |||||
MudSystem%ChokeLine_KickLoc = i | |||||
exit | |||||
endif | |||||
end do | |||||
! ============================ must be after migration-end =========================== | |||||
IF (ALLOCATED(GasPocketWeight%Array) .and. KickNumber == MudSystem%NewInfluxNumber .AND. NOT(KickOffBottom) .AND. MudSystem%WellHeadIsOpen) THEN | |||||
cycle | |||||
ELSE IF (ALLOCATED(GasPocketWeight%Array)) THEN | |||||
if (((GasPocketDeltaVol%Array(MudSystem%NewInfluxNumber - KickNumber + 1) > 0.0 .AND. MudSystem%WellHeadIsOpen) .or. MudSystem%Kickexpansion_DueToMudLost) ) call Kick_Expansion | |||||
if ((GasPocketDeltaVol%Array(MudSystem%NewInfluxNumber - KickNumber + 1) < 0.0 ) .OR. MudSystem%WellHeadIsOpen == .FALSE.) CALL Kick_Contraction | |||||
ENDIF | |||||
ENDDO | |||||
MudSystem%KickNumber = KickNumber | |||||
MudSystem%LostInTripOutIsDone= .false. | |||||
if( MudSystem%DeltaVolumeOp >= 0.0 .and. Get_KellyConnection()==KELLY_CONNECTION_STRING) then | |||||
!write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp | |||||
call Pump_and_TripIn | |||||
elseif (MudSystem%DeltaVolumeOp < 0.0) then | |||||
! when we have Utube and tripping out simultaneously, it uses "TripOut_and_Pump" subroutine, and then Utube code is done | |||||
! "Utube" and "Pump_and_TripIn" subroutines, not to be used simultaneously because "Utube" code supports trip in | |||||
call TripOut_and_Pump | |||||
endif | |||||
MudSystem%WellOutletDensity= MudSystem%Ann_Density%Last() ! (ppg) used in MudSystem | |||||
if (MUD(4)%Q > 0.) then ! ( j4 > 0 ) ! THIS CIRCULATION CODE IS JUST FOR LINE J4, AND NOT NEEDED FOR LINE J18 | |||||
call ChokeLineMud | |||||
endif | |||||
call Choke_GasSound | |||||
!WRITE(*,*) 'CIRCU-Ann_Saved_MudDischarged_Volume' , Ann_Saved_MudDischarged_Volume | |||||
!****Utube is called in Plot Subroutine**** | |||||
Call Instructor_CirculationMud_Edit | |||||
call PlotFinalMudElements | |||||
MudSystem%MudChecked= .true. | |||||
MudSystem%UtubePossibility= .true. | |||||
!WRITE(*,*) '***********************************************************************' | |||||
end subroutine CirculationCodeSelect |
@@ -0,0 +1,186 @@ | |||||
subroutine DEALLOCATE_ARRAYS_NormalCirculation() ! is called in module FluidFlowMain | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
if(allocated(MudSystem%Xstart_PipeSection)) deallocate(MudSystem%Xstart_PipeSection) | |||||
if(allocated(MudSystem%Xend_PipeSection)) deallocate(MudSystem%Xend_PipeSection) | |||||
if(allocated(MudSystem%PipeSection_VolumeCapacity)) deallocate(MudSystem%PipeSection_VolumeCapacity) | |||||
if(allocated(MudSystem%Area_PipeSectionFt)) deallocate(MudSystem%Area_PipeSectionFt) | |||||
if(allocated(MudSystem%OD_PipeSectionInch)) deallocate(MudSystem%OD_PipeSectionInch) | |||||
if(allocated(MudSystem%ID_PipeSectionInch)) deallocate(MudSystem%ID_PipeSectionInch) | |||||
if(allocated(MudSystem%Xstart_OpSection)) deallocate(MudSystem%Xstart_OpSection) | |||||
if(allocated(MudSystem%Xend_OpSection)) deallocate(MudSystem%Xend_OpSection) | |||||
if(allocated(MudSystem%Area_OpSectionFt)) deallocate(MudSystem%Area_OpSectionFt) | |||||
if(allocated(MudSystem%OD_OpSectionInch)) deallocate(MudSystem%OD_OpSectionInch) | |||||
if(allocated(MudSystem%ID_OpSectionInch)) deallocate(MudSystem%ID_OpSectionInch) | |||||
if(allocated(MudSystem%OpSection_VolumeCapacity)) deallocate(MudSystem%OpSection_VolumeCapacity) | |||||
if(allocated(MudSystem%GeoTypeOp)) deallocate(MudSystem%GeoTypeOp) | |||||
if(allocated(MudSystem%GeoType)) deallocate(MudSystem%GeoType) | |||||
call MudSystem%Hz_MudDischarged_Volume%Empty() | |||||
call MudSystem%Hz_Mud_Backhead_X%Empty() | |||||
call MudSystem%Hz_Mud_Backhead_section%Empty() | |||||
call MudSystem%Hz_Mud_Forehead_X%Empty() | |||||
call MudSystem%Hz_Mud_Forehead_section%Empty() | |||||
call MudSystem%Hz_Density%Empty() | |||||
call MudSystem%Hz_RemainedVolume_in_LastSection%Empty() | |||||
call MudSystem%Hz_EmptyVolume_inBackheadLocation%Empty() | |||||
call MudSystem%Hz_MudOrKick%Empty() | |||||
call MudSystem%St_MudDischarged_Volume%Empty() | |||||
call MudSystem%St_Mud_Backhead_X%Empty() | |||||
call MudSystem%St_Mud_Backhead_section%Empty() | |||||
call MudSystem%St_Mud_Forehead_X%Empty() | |||||
call MudSystem%St_Mud_Forehead_section%Empty() | |||||
call MudSystem%St_Density%Empty() | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Empty() | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Empty() | |||||
call MudSystem%St_MudOrKick%Empty() | |||||
call MudSystem%Ann_MudDischarged_Volume%Empty() | |||||
call MudSystem%Ann_Mud_Backhead_X%Empty() | |||||
call MudSystem%Ann_Mud_Backhead_section%Empty() | |||||
call MudSystem%Ann_Mud_Forehead_X%Empty() | |||||
call MudSystem%Ann_Mud_Forehead_section%Empty() | |||||
call MudSystem%Ann_Density%Empty() | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%Empty() | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%Empty() | |||||
call MudSystem%Ann_MudOrKick%Empty() | |||||
call MudSystem%Ann_CuttingMud%Empty() | |||||
call MudSystem%Op_MudDischarged_Volume%Empty() | |||||
call MudSystem%Op_Mud_Backhead_X%Empty() | |||||
call MudSystem%Op_Mud_Backhead_section%Empty() | |||||
call MudSystem%Op_Mud_Forehead_X%Empty() | |||||
call MudSystem%Op_Mud_Forehead_section%Empty() | |||||
call MudSystem%Op_Density%Empty() | |||||
call MudSystem%Op_RemainedVolume_in_LastSection%Empty() | |||||
call MudSystem%Op_EmptyVolume_inBackheadLocation%Empty() | |||||
call MudSystem%Op_MudOrKick%Empty() | |||||
call MudSystem%ChokeLine_MudDischarged_Volume%Empty() | |||||
call MudSystem%ChokeLine_Mud_Backhead_X%Empty() | |||||
call MudSystem%ChokeLine_Mud_Backhead_section%Empty() | |||||
call MudSystem%ChokeLine_Mud_Forehead_X%Empty() | |||||
call MudSystem%ChokeLine_Mud_Forehead_section%Empty() | |||||
call MudSystem%ChokeLine_Density%Empty() | |||||
call MudSystem%ChokeLine_RemainedVolume_in_LastSection%Empty() | |||||
call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Empty() | |||||
call MudSystem%ChokeLine_MudOrKick%Empty() | |||||
call MudSystem%Xend_MudElement%Empty() | |||||
call MudSystem%Xstart_MudElement%Empty() | |||||
call MudSystem%TVDend_MudElement%Empty() | |||||
call MudSystem%TVDstart_MudElement%Empty() | |||||
call MudSystem%Density_MudElement%Empty() | |||||
call MudSystem%MudGeoType%Empty() | |||||
call MudSystem%PipeID_MudElement%Empty() | |||||
call MudSystem%PipeOD_MudElement%Empty() | |||||
call MudSystem%MudType_MudElement%Empty() | |||||
call MudSystem%Xend_OpMudElement%Empty() | |||||
call MudSystem%Xstart_OpMudElement%Empty() | |||||
call MudSystem%TVDend_OpMudElement%Empty() | |||||
call MudSystem%TVDstart_OpMudElement%Empty() | |||||
call MudSystem%Density_OpMudElement%Empty() | |||||
call MudSystem%PipeID_OpMudElement%Empty() | |||||
call MudSystem%PipeOD_OpMudElement%Empty() | |||||
call MudSystem%MudTypeOp_MudElement%Empty() | |||||
end subroutine | |||||
subroutine RemoveAnnulusMudArrays(ilocal) | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
INTEGER :: ilocal | |||||
call MudSystem%Ann_MudDischarged_Volume%Remove (ilocal) | |||||
call MudSystem%Ann_Mud_Backhead_X%Remove (ilocal) | |||||
call MudSystem%Ann_Mud_Backhead_section%Remove (ilocal) | |||||
call MudSystem%Ann_Mud_Forehead_X%Remove (ilocal) | |||||
call MudSystem%Ann_Mud_Forehead_section%Remove (ilocal) | |||||
call MudSystem%Ann_Density%Remove (ilocal) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%Remove (ilocal) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (ilocal) | |||||
call MudSystem%Ann_MudOrKick%Remove (ilocal) | |||||
call MudSystem%Ann_CuttingMud%Remove (ilocal) | |||||
end subroutine | |||||
subroutine RemoveStringMudArrays(ilocal) | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
INTEGER :: ilocal | |||||
call MudSystem%St_MudDischarged_Volume%Remove (ilocal) | |||||
call MudSystem%St_Mud_Backhead_X%Remove (ilocal) | |||||
call MudSystem%St_Mud_Backhead_section%Remove (ilocal) | |||||
call MudSystem%St_Mud_Forehead_X%Remove (ilocal) | |||||
call MudSystem%St_Mud_Forehead_section%Remove (ilocal) | |||||
call MudSystem%St_Density%Remove (ilocal) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Remove (ilocal) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Remove (ilocal) | |||||
call MudSystem%St_MudOrKick%Remove (ilocal) | |||||
end subroutine | |||||
subroutine RemoveOpMudArrays(ilocal) | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
INTEGER :: ilocal | |||||
call MudSystem%Op_MudDischarged_Volume%Remove (ilocal) | |||||
call MudSystem%Op_Mud_Backhead_X%Remove (ilocal) | |||||
call MudSystem%Op_Mud_Backhead_section%Remove (ilocal) | |||||
call MudSystem%Op_Mud_Forehead_X%Remove (ilocal) | |||||
call MudSystem%Op_Mud_Forehead_section%Remove (ilocal) | |||||
call MudSystem%Op_Density%Remove (ilocal) | |||||
call MudSystem%Op_RemainedVolume_in_LastSection%Remove (ilocal) | |||||
call MudSystem%Op_EmptyVolume_inBackheadLocation%Remove (ilocal) | |||||
call MudSystem%Op_MudOrKick%Remove (ilocal) | |||||
end subroutine | |||||
subroutine RemoveHzMudArrays(ilocal) | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
INTEGER :: ilocal | |||||
call MudSystem%Hz_MudDischarged_Volume%Remove (ilocal) | |||||
call MudSystem%Hz_Mud_Backhead_X%Remove (ilocal) | |||||
call MudSystem%Hz_Mud_Backhead_section%Remove (ilocal) | |||||
call MudSystem%Hz_Mud_Forehead_X%Remove (ilocal) | |||||
call MudSystem%Hz_Mud_Forehead_section%Remove (ilocal) | |||||
call MudSystem%Hz_Density%Remove (ilocal) | |||||
call MudSystem%Hz_RemainedVolume_in_LastSection%Remove (ilocal) | |||||
call MudSystem%Hz_EmptyVolume_inBackheadLocation%Remove (ilocal) | |||||
call MudSystem%Hz_MudOrKick%Remove (ilocal) | |||||
end subroutine | |||||
@@ -0,0 +1,108 @@ | |||||
subroutine DisconnectingPipe ! is called in subroutine CirculationCodeSelect | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
use KickVARIABLESModule | |||||
USE TD_DrillStemComponents | |||||
Use CKellyConnectionEnumVariables | |||||
Use CUnityOutputs | |||||
USE CManifolds | |||||
implicit none | |||||
Real(8) ExcessMudVolume, ExcessMudVolume_Remained | |||||
write(*,*) 'DisconnectingPipe' | |||||
!TD_RemoveVolume= TD_RemoveVolume* 7.48051948 ! ft^3 to gal | |||||
ExcessMudVolume= sum(MudSystem%St_MudDischarged_Volume%Array(:)) - sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts)) | |||||
! ======if(ExcessMudVolume <= 0.) No Modification Needed Because Removed Pipe was Empty===== | |||||
if (Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and. Manifold%Valve(56)%Status == .False.) ExcessMudVolume= 0.d0 !Valve(56)%Status == .False. :: safety valve installed | |||||
if (ExcessMudVolume > 0.) then | |||||
if ( Manifold%Valve(53)%Status == .true. ) then | |||||
MudSystem%MudBucketVolume= ExcessMudVolume | |||||
else | |||||
MudSystem%MudBucketVolume= 0.0 | |||||
endif | |||||
!========================Flow Disconnect Unity Input Signals================= | |||||
!if ( Get_JointConnectionPossible() == .false. ) then | |||||
if (Get_KellyConnection() == KELLY_CONNECTION_NOTHING) then | |||||
Call Set_FlowKellyDisconnect(.true.) | |||||
else | |||||
Call Set_FlowPipeDisconnect(.true.) | |||||
endif | |||||
!endif | |||||
!====================Flow Disconnect Unity Input Signals-End================= | |||||
!========================Disconnecting Pipe from the String================= | |||||
ExcessMudVolume_Remained= ExcessMudVolume ! ft^3 to gal | |||||
imud=1 | |||||
Do | |||||
if(MudSystem%St_MudDischarged_Volume%Array(imud) < ExcessMudVolume_Remained) then | |||||
ExcessMudVolume_Remained= ExcessMudVolume_Remained- MudSystem%St_MudDischarged_Volume%Array(imud) | |||||
call MudSystem%St_MudDischarged_Volume%Remove (imud) | |||||
call MudSystem%St_Mud_Backhead_X%Remove (imud) | |||||
call MudSystem%St_Mud_Backhead_section%Remove (imud) | |||||
call MudSystem%St_Mud_Forehead_X%Remove (imud) | |||||
call MudSystem%St_Mud_Forehead_section%Remove (imud) | |||||
call MudSystem%St_Density%Remove (imud) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Remove (imud) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Remove (imud) | |||||
call MudSystem%St_MudOrKick%Remove (imud) | |||||
elseif(MudSystem%St_MudDischarged_Volume%Array(imud) > ExcessMudVolume_Remained) then | |||||
MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- ExcessMudVolume_Remained | |||||
exit | |||||
else !(St_MudDischarged_Volume%Array(imud) == ExcessMudVolume_Remained) | |||||
call MudSystem%St_MudDischarged_Volume%Remove (imud) | |||||
call MudSystem%St_Mud_Backhead_X%Remove (imud) | |||||
call MudSystem%St_Mud_Backhead_section%Remove (imud) | |||||
call MudSystem%St_Mud_Forehead_X%Remove (imud) | |||||
call MudSystem%St_Mud_Forehead_section%Remove (imud) | |||||
call MudSystem%St_Density%Remove (imud) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Remove (imud) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Remove (imud) | |||||
call MudSystem%St_MudOrKick%Remove (imud) | |||||
exit | |||||
endif | |||||
enddo | |||||
!=================Disconnecting Pipe from the String - End=================== | |||||
endif | |||||
end subroutine DisconnectingPipe |
@@ -0,0 +1,274 @@ | |||||
subroutine ElementsCreation ! is called in subroutine Fluid_Flow_Solver | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
!USE CHOKEVARIABLES | |||||
!USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure | |||||
!use CManifolds | |||||
use CDrillWatchVariables | |||||
!use CHOKEVARIABLES | |||||
!use CChokeManifoldVariables | |||||
! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
use KickVARIABLESModule | |||||
use CError | |||||
implicit none | |||||
integer jelement, jmud, jsection,ielement,i | |||||
integer jopelement,jopmud,jopsection,iisection,isection,OpSection | |||||
!===========================================================WELL============================================================ | |||||
!===========================================================WELL============================================================ | |||||
if(allocated(MudSystem%Xstart_PipeSection)) deallocate(MudSystem%Xstart_PipeSection) | |||||
if(allocated(MudSystem%Xend_PipeSection)) deallocate(MudSystem%Xend_PipeSection) | |||||
if(allocated(MudSystem%PipeSection_VolumeCapacity)) deallocate(MudSystem%PipeSection_VolumeCapacity) | |||||
if(allocated(MudSystem%Area_PipeSectionFt)) deallocate(MudSystem%Area_PipeSectionFt) | |||||
if(allocated(MudSystem%GeoType)) deallocate(MudSystem%GeoType) | |||||
if(allocated(MudSystem%OD_PipeSectionInch)) deallocate(MudSystem%OD_PipeSectionInch) | |||||
if(allocated(MudSystem%ID_PipeSectionInch)) deallocate(MudSystem%ID_PipeSectionInch) | |||||
if(allocated(MudSystem%Angle_PipeSection)) deallocate(MudSystem%Angle_PipeSection) | |||||
if(allocated(MudSystem%Xstart_OpSection)) deallocate(MudSystem%Xstart_OpSection) | |||||
if(allocated(MudSystem%Xend_OpSection)) deallocate(MudSystem%Xend_OpSection) | |||||
if(allocated(MudSystem%OpSection_VolumeCapacity)) deallocate(MudSystem%OpSection_VolumeCapacity) | |||||
if(allocated(MudSystem%Area_OpSectionFt)) deallocate(MudSystem%Area_OpSectionFt) | |||||
if(allocated(MudSystem%GeoTypeOp)) deallocate(MudSystem%GeoTypeOp) | |||||
if(allocated(MudSystem%OD_OpSectionInch)) deallocate(MudSystem%OD_OpSectionInch) | |||||
if(allocated(MudSystem%ID_OpSectionInch)) deallocate(MudSystem%ID_OpSectionInch) | |||||
if(allocated(MudSystem%Angle_OpSection)) deallocate(MudSystem%Angle_OpSection) | |||||
ALLOCATE (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts),MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts) & | |||||
,MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts),MudSystem%Area_PipeSectionFt(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts), & | |||||
MudSystem%GeoType(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts),MudSystem%OD_PipeSectionInch(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts),MudSystem%ID_PipeSectionInch(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts)) | |||||
ALLOCATE (MudSystem%Xstart_OpSection(F_Counts%BottomHoleIntervalCounts),MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts) & | |||||
,MudSystem%OpSection_VolumeCapacity(F_Counts%BottomHoleIntervalCounts),MudSystem%Area_OpSectionFt(F_Counts%BottomHoleIntervalCounts), & | |||||
MudSystem%GeoTypeOp(F_Counts%BottomHoleIntervalCounts),MudSystem%OD_OpSectionInch(F_Counts%BottomHoleIntervalCounts),MudSystem%ID_OpSectionInch(F_Counts%BottomHoleIntervalCounts)) | |||||
MudSystem%OpSection=0 | |||||
MudSystem%isection=0 | |||||
DO iisection=1, F_Counts%IntervalsTotalCounts | |||||
IF (F_Interval(iisection)%GeoType == 1) THEN | |||||
MudSystem%OpSection= MudSystem%OpSection+1 | |||||
MudSystem%Xstart_OpSection(MudSystem%OpSection)= (F_Interval(iisection)%StartDepth) | |||||
MudSystem%Xend_OpSection(MudSystem%OpSection)= (F_Interval(iisection)%EndDepth) | |||||
MudSystem%Area_OpSectionFt(MudSystem%OpSection)= PII*((F_Interval(iisection)%OD/12.0d0)**2-(F_Interval(iisection)%ID/12.0d0)**2)/4.0d0 !D(in), AREA(ft^2) | |||||
MudSystem%OD_OpSectionInch(MudSystem%OpSection)= (F_Interval(iisection)%OD) | |||||
MudSystem%ID_OpSectionInch(MudSystem%OpSection)= (F_Interval(iisection)%ID) !REAL(F_Interval(iisection)%Volume) | |||||
MudSystem%GeoTypeOp(MudSystem%OpSection)= F_Interval(iisection)%GeoType ! niaz nist ehtemalan | |||||
!Angle_OpSection(OpSection)= F_Interval(iisection)%Angle | |||||
!write(*,*) 'iisection=' , iisection | |||||
!write(*,*) 'StartDepth=' , F_Interval(iisection)%StartDepth | |||||
!write(*,*) 'EndDepth=' , F_Interval(iisection)%EndDepth | |||||
!write(*,*) 'OD=' , F_Interval(iisection)%OD | |||||
!write(*,*) 'ID=' , F_Interval(iisection)%ID | |||||
ELSE | |||||
MudSystem%isection= MudSystem%isection+1 | |||||
MudSystem%Xstart_PipeSection(MudSystem%isection)= (F_Interval(iisection)%StartDepth) | |||||
!write(*,*) 'F_Interval(iisection)%StartDepth=' , F_Interval(iisection)%StartDepth | |||||
MudSystem%Xend_PipeSection(MudSystem%isection)= (F_Interval(iisection)%EndDepth) | |||||
!write(*,*) 'F_Interval(iisection)%EndDepth=' , F_Interval(iisection)%EndDepth | |||||
MudSystem%OD_PipeSectionInch(MudSystem%isection)= (F_Interval(iisection)%OD) | |||||
MudSystem%Area_PipeSectionFt(MudSystem%isection)= PII*((F_Interval(iisection)%OD/12.0d0)**2-(F_Interval(iisection)%ID/12.0d0)**2)/4.0d0 !D(in), AREA(ft^2) | |||||
MudSystem%ID_PipeSectionInch(MudSystem%isection)= (F_Interval(iisection)%ID) | |||||
!PipeSection_VolumeCapacity(isection)= Area_PipeSectionFt(isection)* ABS(Xend_PipeSection(isection)-Xstart_PipeSection(isection))* 7.48051948 !REAL(F_Interval(iisection)%Volume) ! (gal) | |||||
MudSystem%GeoType(MudSystem%isection)= F_Interval(iisection)%GeoType | |||||
!Angle_PipeSection(isection)= F_Interval(iisection)%Angle | |||||
ENDIF | |||||
ENDDO | |||||
call MudSystem%Xstart_MudElement%Empty() | |||||
call MudSystem%Xstart_MudElement%Add(MudSystem%Xstart_PipeSection(1)) | |||||
call MudSystem%Xstart_OpMudElement%Empty() | |||||
call MudSystem%Xstart_OpMudElement%Add(MudSystem%Xstart_OpSection(1)) | |||||
call MudSystem%TVDstart_MudElement%Empty() | |||||
call TVD_Calculator(MudSystem%Xstart_PipeSection(1),MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDstart_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDstart_OpMudElement%Empty() | |||||
call TVD_Calculator(MudSystem%Xstart_OpSection(1),MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDstart_OpMudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
MudSystem%NoPipeSections= MudSystem%isection ! sections in string and annulus(GeoType 0 & 2) | |||||
DO OpSection= 1,F_Counts%BottomHoleIntervalCounts | |||||
MudSystem%OpSection_VolumeCapacity(OpSection)= MudSystem%Area_OpSectionFt(OpSection)* ABS(MudSystem%Xend_OpSection(OpSection)-MudSystem%Xstart_OpSection(OpSection))* 7.48051948d0 !REAL(F_Interval(iisection)%Volume) | |||||
ENDDO | |||||
MudSystem%OpSection=OpSection | |||||
DO isection= 1,MudSystem%NoPipeSections | |||||
MudSystem%PipeSection_VolumeCapacity(isection)= MudSystem%Area_PipeSectionFt(isection)* ABS(MudSystem%Xend_PipeSection(isection)-MudSystem%Xstart_PipeSection(isection))* 7.48051948d0 !REAL(F_Interval(iisection)%Volume) ! (gal) | |||||
ENDDO | |||||
MudSystem%isection = isection | |||||
!types: Mud= 0 Kick=1 | |||||
!=========================================== | |||||
if (MudSystem%FirstMudSet==0) then | |||||
call MudSystem%Hz_MudDischarged_Volume%AddToFirst(MudSystem%PipeSection_VolumeCapacity(1)) !startup initial | |||||
call MudSystem%Hz_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(1)) | |||||
call MudSystem%Hz_Mud_Backhead_section%AddToFirst (1) | |||||
call MudSystem%Hz_Mud_Forehead_X%AddToFirst (MudSystem%Xend_PipeSection(1)) | |||||
call MudSystem%Hz_Mud_Forehead_section%AddToFirst (1) | |||||
call MudSystem%Hz_Density%AddToFirst (MudProperties%ActiveDensity) ! initial(ppg) | |||||
call MudSystem%Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%Hz_MudOrKick%AddToFirst (0) | |||||
call MudSystem%St_MudDischarged_Volume%AddToFirst(sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts))) !startup initial | |||||
call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) | |||||
call MudSystem%St_Mud_Backhead_section%AddToFirst (2) | |||||
call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)) | |||||
call MudSystem%St_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts) | |||||
call MudSystem%St_Density%AddToFirst (MudProperties%ActiveDensity) ! initial(ppg) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%St_MudOrKick%AddToFirst (0) | |||||
call MudSystem%Ann_MudDischarged_Volume%AddToFirst(sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections))) | |||||
call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)) | |||||
call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1) | |||||
call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)) | |||||
call MudSystem%Ann_Mud_Forehead_section%AddToFirst (MudSystem%NoPipeSections) | |||||
call MudSystem%Ann_Density%AddToFirst (MudProperties%ActiveDensity) ! initial(ppg) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%Ann_MudOrKick%AddToFirst (0) | |||||
call MudSystem%Ann_CuttingMud%AddToFirst (0) | |||||
MudSystem%OldPosition= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts) | |||||
MudSystem%OldAnnulusCapacity= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) | |||||
call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst(MudSystem%ChokeLine_VolumeCapacity) | |||||
call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) | |||||
call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1) | |||||
call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (BopStackSpecification%ChokeLineLength) | |||||
call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1) | |||||
call MudSystem%ChokeLine_Density%AddToFirst (MudProperties%ActiveDensity) ! initial(ppg) | |||||
call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%ChokeLine_MudOrKick%AddToFirst (0) | |||||
call MudSystem%Op_MudDischarged_Volume%AddToFirst (sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))) | |||||
call MudSystem%Op_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_OpSection(1)) | |||||
call MudSystem%Op_Mud_Backhead_section%AddToFirst (1) | |||||
call MudSystem%Op_Mud_Forehead_X%AddToFirst (MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) | |||||
call MudSystem%Op_Mud_Forehead_section%AddToFirst (F_Counts%BottomHoleIntervalCounts) | |||||
call MudSystem%Op_Density%AddToFirst (MudProperties%ActiveDensity) | |||||
call MudSystem%Op_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%Op_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%Op_MudOrKick%AddToFirst (0) | |||||
!F_StringIntervalCountsOld= F_StringIntervalCounts ! is used for adding new pipe to string | |||||
MudSystem%F_StringIntervalCounts_Old= F_Counts%StringIntervalCounts ! is used for adding new pipe to string | |||||
MudSystem%FirstMudSet= 1 | |||||
endif | |||||
!===================== Trip Detection ================ | |||||
!DeltaVolumeOp > 0 : Trip in | |||||
!DeltaVolumeOp < 0 : Trip out | |||||
MudSystem%DeltaVolumeOp= ((MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)-MudSystem%OldPosition)*PII*((MudSystem%OD_PipeSectionInch(F_Counts%StringIntervalCounts+1)/12.0d0)**2)/4.0d0)* 7.48051948d0! ft^3 to gal ! D(in) | |||||
MudSystem%DeltaVolumeOp = INT(MudSystem%DeltaVolumeOp * 100000.d0) / 100000.d0 | |||||
MudSystem%DeltaVolumePipe= ((MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)-MudSystem%OldPosition)*PII*((MudSystem%ID_PipeSectionInch(F_Counts%StringIntervalCounts+F_Counts%AnnulusIntervalCounts)/12.0d0)**2)/4.0d0)* 7.48051948d0! ft^3 to gal | |||||
MudSystem%DeltaVolumePipe = INT(MudSystem%DeltaVolumePipe * 100000.d0) / 100000.d0 | |||||
!DeltaVolumeAnnulusCapacity= ((Xend_PipeSection(F_Counts%StringIntervalCounts)-OldPosition))*Area_PipeSectionFt(NoPipeSections)* 7.48051948d0! ft^3 to gal | |||||
DrillStringSpeed = (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)-MudSystem%OldPosition) / 0.1 | |||||
MudSystem%DeltaVolumeAnnulusCapacity= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) - MudSystem%OldAnnulusCapacity | |||||
!write(*,*) 'DeltaVolumeAnnulusCapacity= ' , DeltaVolumeAnnulusCapacity | |||||
!write(*,*) 'DeltaVolumePipe=' , DeltaVolumePipe | |||||
!write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp | |||||
! | |||||
! | |||||
!write(*,*) 'Bit here=' , Xend_PipeSection(F_Counts%StringIntervalCounts) | |||||
MudSystem%OldAnnulusCapacity= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) | |||||
MudSystem%OldPosition= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts) | |||||
! Needed for trip in or out: | |||||
if (MudSystem%Hz_Mud_Backhead_X%Length() == 0) then | |||||
CALL ErrorStop('Hz_Mud_Backhead_X Length is 0') | |||||
endif | |||||
MudSystem%Hz_Mud_Backhead_X%Array(1)= MudSystem%Xstart_PipeSection(1) | |||||
MudSystem%Hz_Mud_Backhead_section%Array(1)= 1 | |||||
MudSystem%AddedElementsToString = F_Counts%StringIntervalCounts - MudSystem%F_StringIntervalCounts_Old | |||||
MudSystem%St_Mud_Backhead_X%Array(1)= MudSystem%Xstart_PipeSection(2) | |||||
MudSystem%St_Mud_Backhead_section%Array(1)= 2 | |||||
MudSystem%Ann_Mud_Backhead_X%Array(1)= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1) | |||||
MudSystem%Ann_Mud_Backhead_section%Array(1)= F_Counts%StringIntervalCounts+1 | |||||
MudSystem%Op_Mud_Backhead_X%Array(1)= MudSystem%Xstart_OpSection(1) | |||||
MudSystem%Op_Mud_Backhead_section%Array(1)= 1 | |||||
MudSystem%ChokeLine_Mud_Backhead_X%Array(1)= 0. | |||||
MudSystem%ChokeLine_Mud_Backhead_section%Array(1)= 1 | |||||
MudSystem%F_StringIntervalCounts_Old= F_Counts%StringIntervalCounts | |||||
!write(*,*) 'Xstart_PipeSection(2)' , Xstart_PipeSection(2) | |||||
!write(*,*) 'Xend_PipeSection(1)' , Xend_PipeSection(1) | |||||
!=================================================== | |||||
! | |||||
!DeltaWellCap= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) + sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) - WellCapOld | |||||
!WellCapOld= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) + sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) | |||||
!write(*,*) 'DeltaWellCap=' , DeltaWellCap | |||||
! | |||||
! | |||||
! | |||||
!DeltaAnnCap= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) - AnnCapOld | |||||
!AnnCapOld= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) | |||||
!write(*,*) 'DeltaAnnCap=' , DeltaAnnCap | |||||
end subroutine ElementsCreation | |||||
@@ -0,0 +1,215 @@ | |||||
subroutine FillingWell_By_BellNipple ! is called in subroutine CirculationCodeSelect | |||||
! this subroutine is for lines: 1) BellNippleToWell-NonFullWell : MUD(8)%Q | |||||
! 2) PumpsToWell_KillLine : MUD(10)%Q | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
use KickVARIABLESModule | |||||
implicit none | |||||
real(8) deltaV,Xposition,FillingDensity | |||||
integer kloc,SectionPosition | |||||
! Well Is Not Full | |||||
if (MudSystem%Ann_MudOrKick%Last() == 104) then ! Last Element is air we must observe: Ann_Mud_Forehead_X%Last()=0.0 | |||||
write(*,*) 'FillingWell_By_BellNipple-Last Element is air' | |||||
!write(*,*) '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last() | |||||
!write(*,*) '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last() | |||||
FillingDensity= MudSystem%BellNippleDensity | |||||
!**************************** | |||||
if ( MudSystem%Ann_MudDischarged_Volume%Last() > (((MUD(8)%Q+MUD(10)%Q)/60.)*MudSystem%DeltaT_Mudline)) then ! air baghi mimune | |||||
kloc= MudSystem%Ann_MudDischarged_Volume%Length()-1 | |||||
deltaV= ((MUD(8)%Q+MUD(10)%Q)/60.)*MudSystem%DeltaT_Mudline | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length()) - deltaV | |||||
!========================ANNULUS ENTRANCE==================== | |||||
if (ABS(MudSystem%Ann_Density%Array(kloc) - FillingDensity) >= MudSystem%DensityMixTol) then ! new mud is pumped | |||||
call MudSystem%Ann_Density%AddTo (kloc, FillingDensity) | |||||
call MudSystem%Ann_MudDischarged_Volume%AddTo (kloc, 0.0d0) | |||||
call MudSystem%Ann_Mud_Forehead_X%AddTo (kloc, 0.0d0) | |||||
call MudSystem%Ann_Mud_Forehead_section%AddTo (kloc, 1) | |||||
call MudSystem%Ann_Mud_Backhead_X%AddTo (kloc, 0.0d0) | |||||
call MudSystem%Ann_Mud_Backhead_section%AddTo (kloc, MudSystem%NoPipeSections) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (kloc, 0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (kloc, 0.0d0) | |||||
call MudSystem%Ann_MudOrKick%AddTo (kloc, 0) | |||||
call MudSystem%Ann_CuttingMud%AddTo (kloc,0) | |||||
!AnnulusSuctionDensity_Old= Hz_Density_Utube | |||||
endif | |||||
!========================ANNULUS==================== | |||||
MudSystem%Ann_MudDischarged_Volume%Array(kloc)= MudSystem%Ann_MudDischarged_Volume%Array(kloc)+ deltaV !(gal) | |||||
else ! ( Ann_MudDischarged_Volume%Last() <= (((MUD(8)%Q+MUD(10)%Q)/60.)*DeltaT_Mudline)) then ! air baghi namune | |||||
kloc= MudSystem%Ann_MudDischarged_Volume%Length()-1 | |||||
deltaV= MudSystem%Ann_MudDischarged_Volume%Last() | |||||
if (ABS(MudSystem%Ann_Density%Array(kloc)-FillingDensity)< MudSystem%DensityMixTol .and. MudSystem%Ann_CuttingMud%Array(kloc)==0) then ! .OR. (Ann_MudDischarged_Volume%Array(kloc)< 42.) ) then ! 1-Pockets are Merged | |||||
MudSystem%Ann_Density%Array(kloc)= (MudSystem%Ann_Density%Array(kloc)*MudSystem%Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(kloc)= MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV | |||||
MudSystem%Ann_Mud_Forehead_X%Array(kloc)= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) | |||||
MudSystem%Ann_Mud_Forehead_section%Array(kloc)= MudSystem%NoPipeSections | |||||
!Ann_Mud_Backhead_X%Array(kloc)= no change | |||||
!Ann_Mud_Backhead_section%Array(kloc)= no change | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0) | |||||
call MudSystem%Ann_MudDischarged_Volume%Remove (kloc+1) | |||||
call MudSystem%Ann_Mud_Backhead_X%Remove (kloc+1) | |||||
call MudSystem%Ann_Mud_Backhead_section%Remove (kloc+1) | |||||
call MudSystem%Ann_Mud_Forehead_X%Remove (kloc+1) | |||||
call MudSystem%Ann_Mud_Forehead_section%Remove (kloc+1) | |||||
call MudSystem%Ann_Density%Remove (kloc+1) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%Remove (kloc+1) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (kloc+1) | |||||
call MudSystem%Ann_MudOrKick%Remove (kloc+1) | |||||
call MudSystem%Ann_CuttingMud%Remove (kloc+1) | |||||
else ! 2-Merging conditions are not meeted, so new pocket== air is replaced with filling mud | |||||
MudSystem%Ann_Density%Array(kloc+1) =FillingDensity | |||||
MudSystem%Ann_MudOrKick%Array(kloc+1)= 0 | |||||
endif | |||||
endif | |||||
! end condition (Ann_MudOrKick%Last() == 104) ! Last Element is air | |||||
!********************************************************************************************************************************************************** | |||||
else ! (Ann_MudOrKick%Last() == 0) then ! Last Element is NOT air- so we must observe: Ann_Mud_Forehead_X%Last()/=0.0 | |||||
!write(*,*) 'FillingWell_By_BellNipple-Last Element is NOT air' | |||||
! | |||||
!write(*,*) '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last() | |||||
!write(*,*) '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last() | |||||
deltaV= ((MUD(8)%Q+MUD(10)%Q)/60.)*MudSystem%DeltaT_Mudline | |||||
kloc= MudSystem%Ann_MudDischarged_Volume%Length() | |||||
!========================ANNULUS ENTRANCE==================== | |||||
if (ABS(MudSystem%Ann_Density%Last() - FillingDensity) >= MudSystem%DensityMixTol .or. MudSystem%Ann_CuttingMud%Last()==1) then ! .OR. (Ann_MudDischarged_Volume%Array(kloc)>42.) ) then ! new mud is pumped | |||||
Xposition= MudSystem%Ann_Mud_Forehead_X%Last() | |||||
SectionPosition= MudSystem%Ann_Mud_Forehead_section%Last() | |||||
call MudSystem%Ann_Density%Add (FillingDensity) | |||||
call MudSystem%Ann_MudDischarged_Volume%Add (0.0d0) | |||||
call MudSystem%Ann_Mud_Forehead_X%Add (Xposition) | |||||
call MudSystem%Ann_Mud_Forehead_section%Add (SectionPosition) | |||||
call MudSystem%Ann_Mud_Backhead_X%Add (Xposition) | |||||
call MudSystem%Ann_Mud_Backhead_section%Add (SectionPosition) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0) | |||||
call MudSystem%Ann_MudOrKick%Add (0) | |||||
call MudSystem%Ann_CuttingMud%Add (0) | |||||
!AnnulusSuctionDensity_Old= Hz_Density_Utube | |||||
!endif | |||||
!========================ANNULUS==================== | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())+ deltaV !(gal) | |||||
else ! Merged with last Mud | |||||
MudSystem%Ann_Density%Array(kloc)= (MudSystem%Ann_Density%Array(kloc)*MudSystem%Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(kloc)= MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV | |||||
!Ann_Mud_Forehead_X%Array(kloc)= Xend_PipeSection(NoPipeSections) | |||||
!Ann_Mud_Forehead_section%Array(kloc)= NoPipeSections | |||||
!Ann_Mud_Backhead_X%Array(kloc)= no change | |||||
!Ann_Mud_Backhead_section%Array(kloc)= no change | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0) | |||||
endif | |||||
endif | |||||
end subroutine FillingWell_By_BellNipple |
@@ -0,0 +1,234 @@ | |||||
subroutine Kick_Expansion ! is called in subroutine CirculationCodeSelect | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
USE CReservoirVariables | |||||
use KickVARIABLESModule | |||||
implicit none | |||||
real(8) ExpansionVolume | |||||
!write(*,*) 'Kick Expansion' | |||||
ExpansionVolume= GasPocketDeltaVol%Array(MudSystem%NewInfluxNumber - MudSystem%KickNumber + 1) * 7.48 | |||||
IF ( MudSystem%Kickexpansion_DueToMudLost ) ExpansionVolume = ((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) | |||||
!============================== kick zire mate bashad ============================== | |||||
if (MudSystem%Op_KickLoc > 0 .and. MudSystem%Ann_KickLoc==0) then ! .and. Op_KickLoc /= Op_MudOrKick%Length ()) then | |||||
!write(*,*) 'expansion (1)' | |||||
MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_KickLoc)= MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_KickLoc)+ ExpansionVolume | |||||
!if (MUD(4)%Q > 0.) then | |||||
! | |||||
! if (abs(ChokeLine_Density%Array(1)-Ann_Density%Last())< DensityMixTol) then | |||||
! ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1) + ExpansionVolume | |||||
! else | |||||
! call ChokeLine_Density%AddToFirst (Ann_Density%Last()) | |||||
! call ChokeLine_MudDischarged_Volume%AddToFirst (ExpansionVolume) ! farz kardam ke hameye hajm ro ba yek density ezafe konim | |||||
! call ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) | |||||
! call ChokeLine_Mud_Forehead_section%AddToFirst (1) | |||||
! call ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) | |||||
! call ChokeLine_Mud_Backhead_section%AddToFirst (1) | |||||
! call ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! call ChokeLine_MudOrKick%AddToFirst (Ann_MudOrKick%Last()) | |||||
! endif | |||||
! | |||||
!endif | |||||
endif | |||||
!======================================================================================== | |||||
!============================= foreheade dar fazaye annulus bashad =========================== | |||||
! agar kick be entehaye annulus reside bashe, expansion ra emaal nemikonim | |||||
if (MudSystem%Ann_KickLoc > 0) then ! .and. Ann_KickLoc /= Ann_MudOrKick%Length ()) then | |||||
!write(*,*) 'expansion (2)' | |||||
!if ( sum(Ann_MudDischarged_Volume%Array(1:Ann_KickLoc)) + ExpansionVolume > sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ) then ! agar khast az mate rad kone | |||||
! ExpansionVolume= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) - sum(Ann_MudDischarged_Volume%Array(1:Ann_KickLoc)) | |||||
!endif | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_KickLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_KickLoc)+ ExpansionVolume | |||||
!if (MUD(4)%Q > 0.) then | |||||
! | |||||
! | |||||
! if (abs(ChokeLine_Density%Array(1)-Ann_Density%Last())< DensityMixTol) then | |||||
! ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1) + ExpansionVolume | |||||
! else | |||||
! call ChokeLine_Density%AddToFirst (Ann_Density%Last()) | |||||
! call ChokeLine_MudDischarged_Volume%AddToFirst (ExpansionVolume) ! farz kardam ke hameye hajm ro ba yek density ezafe konim | |||||
! call ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) | |||||
! call ChokeLine_Mud_Forehead_section%AddToFirst (1) | |||||
! call ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) | |||||
! call ChokeLine_Mud_Backhead_section%AddToFirst (1) | |||||
! call ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! call ChokeLine_MudOrKick%AddToFirst (Ann_MudOrKick%Last()) | |||||
! endif | |||||
! | |||||
!endif | |||||
endif | |||||
!======================================================================================== | |||||
!=============================== foreheade dar choke line bashad ============================= | |||||
if (MudSystem%ChokeLine_KickLoc > 0 .and. MudSystem%Ann_KickLoc==0) then | |||||
MudSystem%ChokeLine_MudDischarged_Volume%Array(MudSystem%ChokeLine_KickLoc)= MudSystem%ChokeLine_MudDischarged_Volume%Array(MudSystem%ChokeLine_KickLoc)+ ExpansionVolume | |||||
endif | |||||
!======================================================================================== | |||||
!write(*,*) 'Expansion======0' | |||||
! !do imud=1, Ann_MudDischarged_Volume%Length() | |||||
! ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) | |||||
! !enddo | |||||
! | |||||
! do imud=1, Op_MudDischarged_Volume%Length() | |||||
! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) | |||||
! enddo | |||||
!write(*,*) '0======expansion' | |||||
end subroutine Kick_Expansion | |||||
subroutine Kick_Contraction ! is called in subroutine CirculationCodeSelect | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
USE CReservoirVariables | |||||
use KickVARIABLESModule | |||||
USE CError | |||||
implicit none | |||||
integer jelement, jmud, jsection,ielement,i | |||||
integer jopelement,jopmud,jopsection | |||||
real(8) ContractionVolume | |||||
!********************************************************* | |||||
! contraction is always with pump flow | |||||
!********************************************************* | |||||
!write(*,*) 'Kick Contraction' | |||||
!MUD(2)%Q= MPumps%Total_Pump_GPM | |||||
MudSystem%StringFlowRate= MUD(2)%Q | |||||
MudSystem%AnnulusFlowRate= MUD(2)%Q | |||||
if (MudSystem%NewPipeFilling == 0) then | |||||
MudSystem%StringFlowRate= 0. | |||||
MudSystem%AnnulusFlowRate= 0. | |||||
endif | |||||
!if (WellHeadIsOpen) then | |||||
ContractionVolume= - GasPocketDeltaVol%Array(MudSystem%NewInfluxNumber - MudSystem%KickNumber + 1) * 7.48 | |||||
!else | |||||
!ContractionVolume = (MudSystem%StringFlowRate/60.0d0)*DeltaT_Mudline + DeltaVolumePipe | |||||
if (MudSystem%KickNumber == 1 .and. MudSystem%WellHeadIsOpen==.false.) ContractionVolume = ContractionVolume + (MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline + MudSystem%DeltaVolumePipe | |||||
!endif | |||||
!************************************************************************************************************************************************************************** | |||||
! pump mud is added in "pump&TripIn" code | |||||
IF (MudSystem%Op_KickLoc > 0 .and. MudSystem%Ann_KickLoc == 0) then ! All of kick is under bit (iloc == 1) | |||||
MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_KickLoc)= MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_KickLoc) - ( ContractionVolume ) | |||||
ELSE IF (MudSystem%Op_KickLoc == 0 .AND. MudSystem%Ann_KickLoc > 0 .AND. MudSystem%ChokeLine_KickLoc == 0) THEN ! All of kick is an Annulus (iloc == 1) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_KickLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_KickLoc) - ( ContractionVolume ) | |||||
ELSE IF (MudSystem%Ann_KickLoc == 0 .AND. MudSystem%ChokeLine_KickLoc > 0) THEN ! kick is in chokeline only | |||||
MudSystem%ChokeLine_MudDischarged_Volume%Array(MudSystem%ChokeLine_KickLoc)= MudSystem%ChokeLine_MudDischarged_Volume%Array(MudSystem%ChokeLine_KickLoc) - ( ContractionVolume ) | |||||
ELSE IF (MudSystem%Op_KickLoc > 0 .AND. MudSystem%Ann_KickLoc > 0) THEN ! Kick is around bit (iloc==2) | |||||
if (MudSystem%Ann_MudDischarged_Volume%Array(1) > ContractionVolume ) then | |||||
MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) - ( ContractionVolume ) | |||||
elseif (MudSystem%Op_MudDischarged_Volume%Last() > ContractionVolume ) then | |||||
MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_MudDischarged_Volume%Length())= MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_MudDischarged_Volume%Length()) - ( ContractionVolume ) | |||||
else | |||||
Call ErrorStop ('kick contraction error 1') | |||||
endif | |||||
ELSE IF (MudSystem%Ann_KickLoc > 0 .AND. MudSystem%ChokeLine_KickLoc > 0) THEN | |||||
if (MudSystem%ChokeLine_MudDischarged_Volume%Array(1) > ContractionVolume ) then | |||||
MudSystem%ChokeLine_MudDischarged_Volume%Array(1) = MudSystem%ChokeLine_MudDischarged_Volume%Array(1) - ( ContractionVolume ) | |||||
elseif (MudSystem%Ann_MudDischarged_Volume%Last() > ContractionVolume ) then | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length()) - ( ContractionVolume ) | |||||
else | |||||
Call ErrorStop ('kick contraction error 2') | |||||
endif | |||||
endif | |||||
! write(*,*) 'contract======0' | |||||
!! !do imud=1, Ann_MudDischarged_Volume%Length() | |||||
!! ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) | |||||
!! !enddo | |||||
!! | |||||
! do imud=1, Op_MudDischarged_Volume%Length() | |||||
! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) | |||||
! enddo | |||||
!write(*,*) '0======contract' | |||||
end subroutine Kick_Contraction |
@@ -0,0 +1,215 @@ | |||||
subroutine Kick_Influx ! is called in subroutine CirculationCodeSelect | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
use KickVARIABLESModule | |||||
implicit none | |||||
!===========================================================WELL============================================================ | |||||
!===========================================================WELL============================================================ | |||||
!write(*,*) 'Kick Influx' | |||||
!=================== Bottom Hole Kick Influx ENTRANCE(due to Kick) =================== | |||||
MudSystem%Kick_Density= 2 | |||||
MudSystem%NewInflux_Density= MudSystem%Kick_Density | |||||
if ( MudSystem%NewInfluxElementCreated==0 ) then ! new kick is pumped- (it is set to zero in sheykh subroutine after a new kick influx) | |||||
call MudSystem%Op_Density%AddToFirst (MudSystem%NewInflux_Density) | |||||
call MudSystem%Op_MudDischarged_Volume%AddToFirst (0.0d0) | |||||
call MudSystem%Op_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_OpSection(1)) | |||||
call MudSystem%Op_Mud_Forehead_section%AddToFirst (1) | |||||
call MudSystem%Op_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_OpSection(1)) | |||||
call MudSystem%Op_Mud_Backhead_section%AddToFirst (1) | |||||
call MudSystem%Op_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%Op_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%Op_MudOrKick%AddToFirst (MudSystem%NewInfluxNumber) ! KickNumber= NewInfluxNumber | |||||
MudSystem%NewInfluxElementCreated= 1 | |||||
endif | |||||
MudSystem%Op_MudDischarged_Volume%Array(1)= MudSystem%Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) due to KickFlux | |||||
!write(*,*) 'kick volume ok=' , Op_MudDischarged_Volume%Array(1) | |||||
end subroutine Kick_Influx | |||||
subroutine Instructor_CirculationMud_Edit ! is called in subroutine CirculationCodeSelect | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | |||||
USE TD_DrillStemComponents | |||||
Use CUnityInputs | |||||
Use CUnityOutputs | |||||
USE CKellyConnectionEnumVariables | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | |||||
use sROP_Other_Variables | |||||
use CDownHoleVariables | |||||
implicit none | |||||
if ( DownHole%AnnDrillMud == .true. .and. (ROP_Bit%RateOfPenetration>0. .and. MudSystem%DeltaVolumeOp>0.0) ) then | |||||
do imud= 1, MudSystem%Ann_Density%Length() | |||||
if ( MudSystem%Ann_MudOrKick%Array(imud) == 0 ) then | |||||
MudSystem%Ann_Density%Array(imud)= (MudSystem%St_Density%Last() * MudSystem%AnnulusFlowRate + 141.4296E-4*ROP_Bit%RateOfPenetration*ROP_Spec%DiameterOfBit**2)/(MudSystem%AnnulusFlowRate+6.7995E-4*ROP_Bit%RateOfPenetration*ROP_Spec%DiameterOfBit**2) | |||||
MudSystem%Ann_CuttingMud%Array(imud)= 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
if ( DownHole%AnnCirculateMud == .true. ) then | |||||
do imud= 1, MudSystem%Ann_Density%Length() | |||||
if ( MudSystem%Ann_MudOrKick%Array(imud) == 0 ) then | |||||
MudSystem%Ann_Density%Array(imud)= MudSystem%ActiveTankDensity | |||||
MudSystem%Ann_CuttingMud%Array(imud)= 0 | |||||
endif | |||||
enddo | |||||
do imud= 1, MudSystem%St_Density%Length() | |||||
MudSystem%St_Density%Array(imud)= MudSystem%ActiveTankDensity | |||||
enddo | |||||
endif | |||||
end subroutine Instructor_CirculationMud_Edit | |||||
subroutine ShoeLostSub ! is called in subroutine CirculationCodeSelect | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | |||||
USE TD_DrillStemComponents | |||||
Use CUnityInputs | |||||
Use CUnityOutputs | |||||
USE CKellyConnectionEnumVariables | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | |||||
use sROP_Other_Variables | |||||
use CDownHoleVariables | |||||
use CShoeVariables | |||||
use PressureDisplayVARIABLESModule | |||||
Use CWarningsVariables | |||||
implicit none | |||||
MudSystem%ShoeLost= .false. | |||||
MudSystem%Kickexpansion_DueToMudLost= .false. | |||||
MudSystem%ShoeMudPressure= PressureGauges(5) | |||||
MudSystem%UGBOSuccessionCounter = MudSystem%UGBOSuccessionCounter + 1 | |||||
!write(*,*) 'check point 1' | |||||
if (Shoe%InactiveFracture == .FALSE. .AND. ((MudSystem%ShoeMudPressure >= MudSystem%FormationLostPressure) .or. MudSystem%ShoeFractured )) then | |||||
!write(*,*) 'check point 2 ,UGBOSuccessionCounter' , UGBOSuccessionCounter | |||||
! if ShoeFractured changed to true , then time counter is not needed more | |||||
if ( MudSystem%UGBOSuccessionCounter /= MudSystem%UGBOSuccessionCounterOld+1 .and. MudSystem%ShoeFractured==.false. ) then | |||||
MudSystem%UGBOSuccessionCounter = 0 ! also in starup | |||||
MudSystem%UGBOSuccessionCounterOld = 0 ! also in starup | |||||
return | |||||
else | |||||
MudSystem%UGBOSuccessionCounterOld= MudSystem%UGBOSuccessionCounter | |||||
endif | |||||
if ( MudSystem%UGBOSuccessionCounter < 10 .and. MudSystem%ShoeFractured==.false.) then | |||||
return | |||||
endif | |||||
!write(*,*) 'check point 3 ,UGBOSuccessionCounter' , UGBOSuccessionCounter | |||||
MudSystem%ShoeFractured= .true. | |||||
MudSystem%ShoeMudViscosity= MAX(MudSystem%ShoeMudViscosity, 12.d0) | |||||
!write(*,*) 'ShoeMudDensity , ShoeMudViscosity' , ShoeMudDensity , ShoeMudViscosity | |||||
MudSystem%ShoeLostCoef = 10.**(-8) * 1.15741d0 * 7.08d0 * 1000000.d0 * 1.d0 * MudSystem%ShoeMudDensity / & | |||||
(MudSystem%ShoeMudViscosity * LOG(10000.d0)) | |||||
!write(*,*) 'lost parameters 1' , ShoeMudPressure , FormationLostPressure | |||||
MudSystem%Qlost = MAX( (MudSystem%ShoeLostCoef * (MudSystem%ShoeMudPressure - (MudSystem%FormationLostPressure/2.0))) , 0.d0 ) | |||||
if (MudSystem%Qlost > 0.0) then | |||||
MudSystem%ShoeLost= .true. | |||||
else | |||||
MudSystem%ShoeLost= .false. | |||||
endif | |||||
!write(*,*) 'Qlost=' , Qlost, ShoeMudPressure, FormationLostPressure | |||||
call Activate_UndergroundBlowout() | |||||
do imud= 1, MudSystem%Ann_Mud_Forehead_X%Length() | |||||
IF ( MudSystem%ShoeLost .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) & | |||||
.and. MudSystem%Ann_MudOrKick%Array(imud) == 0 .and. MudSystem%WellHeadIsOpen == .FALSE. ) then | |||||
MudSystem%Kickexpansion_DueToMudLost= .true. | |||||
write(*,*) 'Kickexpansion_DueToMudLost' | |||||
EXIT | |||||
ENDIF | |||||
enddo | |||||
endif | |||||
if (Warmings%UndergroundBlowout == .false.) MudSystem%ShoeLost= .false. | |||||
end subroutine ShoeLostSub | |||||
@@ -0,0 +1,85 @@ | |||||
module MudSystemMain | |||||
implicit none | |||||
public | |||||
contains | |||||
! subroutine MudSystem_Setup() | |||||
! ! use CSimulationVariables | |||||
! use MudSystemModule | |||||
! implicit none | |||||
! call SetupMudSystem() | |||||
! call OnSimulationStop%Add(MudSystem_Stop) | |||||
! call OnMudSystemStart%Add(MudSystem_Start) | |||||
! call OnMudSystemStep%Add(MudSystem_Step) | |||||
! call OnMudSystemMain%Add(MudSystemMainBody) | |||||
! end subroutine | |||||
subroutine MudSystem_Stop | |||||
implicit none | |||||
!print* , 'MudSystem_Stop' | |||||
CALL DEALLOCATE_ARRAYS_MudSystem() | |||||
end subroutine MudSystem_Stop | |||||
subroutine MudSystem_Init | |||||
implicit none | |||||
!print* , 'MudSystem_Start' | |||||
CALL MudSystem_StartUp() | |||||
end subroutine MudSystem_Init | |||||
subroutine MudSystem_Step | |||||
use MudSystemModule | |||||
use CManifolds | |||||
implicit none | |||||
!print* , 'MudSystem_Step' | |||||
!CALL main | |||||
if(Manifold%IsTraverse) then | |||||
call LineupAndPath() | |||||
Manifold%IsTraverse = .false. | |||||
endif | |||||
call main() | |||||
end subroutine MudSystem_Step | |||||
! subroutine MudSystemMainBody | |||||
! ! use CSimulationVariables | |||||
! use MudSystemModule | |||||
! implicit none | |||||
! INTEGER :: MudDuration | |||||
! integer,dimension(8) :: MudStartTime , MudEndTime | |||||
! | |||||
!CALL MudSystem_StartUp() | |||||
! loop1: DO | |||||
! | |||||
! CALL DATE_AND_TIME(values=MudStartTime) | |||||
! !WRITE (*,*) '***MudSys_timeCounter', MudSys_timeCounter | |||||
! | |||||
! | |||||
! CALL main | |||||
! | |||||
! CALL DATE_AND_TIME(values=MudEndTime) | |||||
! | |||||
! MudDuration = 3600000 * (MudEndTime(5) - MudStartTime(5)) + 60000 * (MudEndTime(6) - MudStartTime(6)) + 1000 * (MudEndTime(7) - MudStartTime(7)) + (MudEndTime(8) - MudStartTime(8)) | |||||
! | |||||
! if (MudDuration < 100) then | |||||
! ELSE | |||||
! WRITE (*,*) 'Mud System run duration exceeded 100 ms and =', MudDuration | |||||
! end if | |||||
! | |||||
! IF (IsStopped==.true.) THEN | |||||
! EXIT loop1 | |||||
! ENDIF | |||||
! | |||||
! !CALL DATE_AND_TIME(values=FlowEndTime) | |||||
! !WRITE (*,*) 'FlowEndTime=' , FlowEndTime | |||||
! | |||||
! !FlowDuration = FlowEndTime(8) - FlowStartTime(8) | |||||
! | |||||
! !WRITE (*,*) 'FlowDuration Mud system=' , FlowDuration | |||||
! | |||||
! ENDDO loop1 | |||||
! | |||||
! CALL DEALLOCATE_ARRAYS_MudSystem() | |||||
! end subroutine MudSystemMainBody | |||||
end module MudSystemMain |
@@ -0,0 +1,501 @@ | |||||
SUBROUTINE NormalCirculation_StartUp() ! is called in module FluidFlowMain | |||||
USE MudSystemVARIABLES | |||||
use CTanksVariables | |||||
USE CMudPropertiesVariables | |||||
Use GeoElements_FluidModule | |||||
use KickVARIABLESModule | |||||
Use CUnityOutputs | |||||
Use CShoeVariables | |||||
USE Pumps_VARIABLES | |||||
implicit none | |||||
! temporary varibales for solving pressure jerks -- 1399-11-09 | |||||
!Pump1BlownInTimeStep = 0 | |||||
!Pump2BlownInTimeStep = 0 | |||||
!Pump3BlownInTimeStep = 0 | |||||
!Pump1BlownStarted = .FALSE. | |||||
!Pump2BlownStarted = .FALSE. | |||||
!Pump3BlownStarted = .FALSE. | |||||
MudSystem%Pump1BlownCount = 0 | |||||
MudSystem%Pump2BlownCount = 0 | |||||
MudSystem%Pump3BlownCount = 0 | |||||
MudSystem%DeltaWellCap=0. | |||||
MudSystem%WellCapOld = 0. | |||||
MudSystem%AnnCapOld=0. | |||||
MudSystem%DeltaAnnCap=0. | |||||
MPumps%Total_Stroke_Counter_For_Plot = 0.0 | |||||
MudSystem%DeltaT_Mudline=0.1 !second | |||||
Call Set_FlowKellyDisconnect(.false.) | |||||
Call Set_FlowPipeDisconnect(.false.) | |||||
!HZ_ADD= 0.d0 | |||||
MudSystem%Flow_timeCounter= 0 | |||||
MudSystem%MudSys_timeCounter= 0 | |||||
MudSystem%FluidFlowCounter = 0 | |||||
!======================================================================== | |||||
! MUD CIRCULATION STARTUP | |||||
!======================================================================== | |||||
MudSystem%FormationLostPressure= Shoe%LeakOff * Shoe%ShoeDepth | |||||
MudSystem%ShoeFractured= .false. | |||||
MudSystem%UGBOSuccessionCounter = 0 ! also in starup | |||||
MudSystem%UGBOSuccessionCounterOld = 0 ! also in starup | |||||
MudSystem%ChokeLineFlowRate= 0.0 | |||||
MudSystem%StringFlowRate= 0.0 | |||||
MudSystem%AnnulusFlowRate= 0.0 | |||||
MudSystem%MudVolume_InjectedFromAnn= 0.D0 | |||||
MudSystem%MudVolume_InjectedToBH= 0.D0 | |||||
MudSystem%DensityMixTol= 0.1 !(ppg) | |||||
MudSystem%CuttingDensityMixTol= 0.5 | |||||
MudSystem%NewPipeFilling= 1 | |||||
MudSystem%UtubeFilling= 1 | |||||
MudSystem%UtubeEmptyVolume= 0.0 | |||||
MudSystem%UtubeMode1Activated= .false. | |||||
MudSystem%UtubeMode2Activated= .false. | |||||
MudSystem%UtubePossibility= .false. | |||||
!KickMigration_2SideBit = .FALSE. | |||||
MudSystem%KickDx= (Reservoir%AutoMigrationRate/3600.)*MudSystem%DeltaT_Mudline !AutoMigrationRate (ft/h)= ft per DeltaT_Mudline | |||||
MudSystem%NewInfluxElementCreated= 0 | |||||
MudSystem%NewInfluxNumber= 0 | |||||
!KickVolumeinAnnulus= 0.0 | |||||
MudSystem%KickDeltaVinAnnulus= 0.0 | |||||
GasKickPumpFlowRate= 0.0 | |||||
MudSystem%FirstMudSet= 0 | |||||
MudSystem%FirstSetUtube1=0 | |||||
MudSystem%FirstSetUtube2=0 | |||||
MudSystem%SuctionMud=1 | |||||
MudSystem%ImudCount= 1 | |||||
imud=1 | |||||
MudSystem%iLoc= 1 ! for Kick | |||||
MudSystem%Suction_Density_MudSystem= MudProperties%ActiveDensity | |||||
MudSystem%SuctionDensity_Old= MudProperties%ActiveDensity ! initial(ppg) | |||||
MudSystem%StringDensity_Old= MudProperties%ActiveDensity ! initial(ppg) | |||||
MudSystem%AnnulusSuctionDensity_Old= MudProperties%ActiveDensity ! initial(ppg) | |||||
MudSystem%ChokeLineDensity_Old= MudProperties%ActiveDensity ! initial(ppg) | |||||
MudSystem%TotalAddedVolume= 0. | |||||
MudSystem%xx=0. | |||||
END SUBROUTINE NormalCirculation_StartUp | |||||
SUBROUTINE MudSystem_StartUp() | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE CDataDisplayConsoleVariables | |||||
USE CHOKEVARIABLES | |||||
USE Pumps_VARIABLES | |||||
USE CBopStackVariables | |||||
USE CPumpsVariables | |||||
use CTanksVariables | |||||
use KickVARIABLESModule | |||||
implicit none | |||||
CALL MUDLINE_LOSS_INPUTS() | |||||
!MPumps%Total_Pump_GPM=10. ! Initial Value | |||||
MUD%Q=0. ! Initial Value | |||||
MudSystem%Q_flow32=0. | |||||
MudSystem%Q_flow33=0. | |||||
MudSystem%Q_flow34=0. | |||||
MudSystem%Q_flow35=0. | |||||
MudSystem%DeltaT_Mudline=0.1 !second | |||||
GasKickPumpFlowRate= 0. | |||||
MudSystem%BellNippleVolume= 0. | |||||
MudSystem%BellNippleDensity= 0. | |||||
MudSystem%MudBucketVolume= 0. | |||||
MudSystem%MudBucketDensity= 0. | |||||
MudSystem%BellNippleDumpVolume= 0. | |||||
!BellNippleDumpRate= 0. | |||||
!BellNippleToPitsRate= 0.0 | |||||
MudSystem%MudChecked= .true. | |||||
MudSystem%condition32Final= .TRUE. | |||||
MudSystem%condition33Final= .TRUE. | |||||
MudSystem%condition34Final= .TRUE. | |||||
MudSystem%PressureGauge75= 0.0 | |||||
MudSystem%PressureGauge76 = 0.0 | |||||
!!====================================================================== | |||||
!! TRIP TANK | |||||
!!====================================================================== | |||||
MudSystem%TripTank_MinVol_Allowded= 50.*42. !(bbl to gal, initial value) | |||||
MudSystem%TripTank_MaxVol_Allowded= 50. *42. !(bbl to gal, initial value) | |||||
MudSystem%ActiveTankFloorArea= (MudProperties%ActiveTotalTankCapacityGal) / (7.48051948*100./12.) ! (ft^2) - Tank Height= 100 inch , 12=inch to ft 7.48051948=gal to ft^3 | |||||
MudSystem%TripTankFloorArea= (50.*42.) / (7.48051948*100./12.) ! (ft^2) - 50.*42.=Trip Tank Capacity in BBl*42= Gal , Tank Height= 100 inch , 12=inch to ft 7.48051948=gal to ft^3 | |||||
MudSystem%TripTank_Vol= MudProperties%InitialTripTankMudVolumeGal !(gal) | |||||
MudSystem%TripTank_Dens= 1. | |||||
DataDisplayConsole%TripTankGauge=0. | |||||
MudSystem%ReturnToTrip_Q= 1. | |||||
MudSystem%ActiveToTrip_Q= 1. | |||||
MudSystem%TripTankPump_Q= .8 | |||||
MudSystem%ReturnToTrip_Dens=1.0 ! ppg(lbm/gal) | |||||
MudSystem%ActiveToTrip_Dens=1.0 | |||||
!!====================================================================== | |||||
!! MUD VOLUME TOTALIZER | |||||
!!====================================================================== | |||||
MudSystem%Mp1Density= 0.0 !(VALVE82) | |||||
MudSystem%Mp2Density= 0.0 !(VALVE83) | |||||
MudSystem%Mp3Density= 0.0 !(VALVE84) | |||||
MudSystem%ReserveTankVolume= MudProperties%ReserveMudVolumeGal ! initial volume (gal) | |||||
MudSystem%ReserveTankDensity= MudProperties%ReserveDensity ! initial | |||||
MudSystem%CementTankVolumeCalc= Tank%CementTankVolume !movaghat--- initial volume (gal) | |||||
MudSystem%CementTankDensityCalc= Tank%CementTankDensity !movaghat--- initial | |||||
MudSystem%PumpsDumpVolume=0.0 | |||||
MudSystem%PumpsDumpFlowRate= 0.0 | |||||
MudSystem%ActiveTankVolume= MudProperties%ActiveMudVolumeGal ! initial volume (gal) | |||||
MudSystem%RefrencePitVolume= MudSystem%ActiveTankVolume/42. !(bbl) | |||||
MudSystem%RefrencePitVolume_DrillWatch= MudSystem%ActiveTankVolume/42. !(bbl) | |||||
MudSystem%MVT_MinVol_Allowded= 0. | |||||
MudSystem%MVT_MaxVol_Allowded= 0. | |||||
MudSystem%MudTank1_vol= MudProperties%ActiveMudVolumeGal/3. ! (gal) | |||||
MudSystem%MudTank2_vol= MudProperties%ActiveMudVolumeGal/3. ! (gal) | |||||
MudSystem%MudTank3_vol= MudProperties%ActiveMudVolumeGal/3. ! (gal) | |||||
MudSystem%ActiveTankSettled= MudProperties%ActiveSettledContentsGal ! (gal) | |||||
MudSystem%MudTank4_vol= MudProperties%InitialTripTankMudVolumeGal ! (gal) | |||||
MudSystem%TripTankVolumeCalc= MudProperties%InitialTripTankMudVolumeGal ! initial volume (gal) | |||||
MudSystem%ActiveTankDensity= MudProperties%ActiveDensity ! initial(ppg) | |||||
MudSystem%TripTankDensityCalc= Tank%TripTankDensity ! initial(ppg) | |||||
MudSystem%ChokeManifoldDumpVolume= 0.0 | |||||
MudSystem%PitGainLossZero= 0. | |||||
MudSystem%PitGainLossZero_Old= MudSystem%PitGainLossZero | |||||
MudSystem%MVTCoarseKnob_Old= DataDisplayConsole%MVTCoarseKnob | |||||
MudSystem%MVTFineKnob_Old= DataDisplayConsole%MVTFineKnob | |||||
MudSystem%FirstSet_Time= .true. | |||||
MudSystem%PedalMeter= MudProperties%PedalFlowMeter !1600. !(gpm) | |||||
MudSystem%ReturnFlowRate=0. | |||||
MudSystem%TotalStrokes1MFFI =0. | |||||
MudSystem%TotalStrokes2MFFI =0. | |||||
MudSystem%TotalStrokesPump1=0. | |||||
MudSystem%TotalStrokesPump2=0. | |||||
MudSystem%GraphTotalStrokes=0. | |||||
Choke%TotalStrokes1 =0. | |||||
Choke%TotalStrokes2 =0. | |||||
end | |||||
SUBROUTINE MUDLINE_LOSS_INPUTS() | |||||
USE MudSystemVARIABLES | |||||
USE CBopStackVariables | |||||
USE CPumpsVariables | |||||
implicit none | |||||
INTEGER I | |||||
!=========================================================================== | |||||
! MUDLINE MINOR LOSSES INPUT | |||||
!=========================================================================== | |||||
MudSystem%NO_MudMinors=4 | |||||
ALLOCATE (MudSystem%MudMinors(MudSystem%NO_MudMinors,4)) | |||||
! ID(INCH) LF CV NOTE(BAR) DESCRIPTION | |||||
MudSystem%MudMinors(1,1)= PumpsSpecification%MudPump1Output | |||||
MudSystem%MudMinors(1,2:4)= (/1.5*8., 0., 0./) !elbow (MLnumber=1,,PumpsToString) | |||||
MudSystem%MudMinors(2,1)= PumpsSpecification%MudPump1Output | |||||
MudSystem%MudMinors(2,2:4)= (/1.5*6., 0., 0./) !elbow (MLnumber=2,,STGaugeToString) | |||||
MudSystem%MudMinors(3,1:4)= (/0., 0., 0., 0./) !elbow (MLnumber=3,,WellToPits) | |||||
MudSystem%MudMinors(4,1)= BopStackSpecification%ChokeLineId | |||||
MudSystem%MudMinors(4,2:4)= (/1.5*7., 0., 0./) !elbow (MLnumber=4,,WellToChokeManifold) | |||||
ALLOCATE (MudSystem%MINORDIAMETER_MUDLINE(MudSystem%NO_MudMinors),MudSystem%AREAMINOR_MUDLINE(MudSystem%NO_MudMinors),MudSystem%LF_MUDLINE(MudSystem%NO_MudMinors),MudSystem%CV_MUDLINE(MudSystem%NO_MudMinors) & | |||||
,MudSystem%NOTE_MUDLINE(MudSystem%NO_MudMinors)) | |||||
DO I=1,MudSystem%NO_MudMinors | |||||
MudSystem%MINORDIAMETER_MUDLINE(I)=MudSystem%MudMinors(I,1) | |||||
MudSystem%LF_MUDLINE(I)=MudSystem%MudMinors(I,2) | |||||
MudSystem%CV_MUDLINE(I)=MudSystem%MudMinors(I,3) | |||||
MudSystem%NOTE_MUDLINE(I)=MudSystem%MudMinors(I,4) | |||||
MudSystem%AREAMINOR_MUDLINE(I)=PII*(MudSystem%MINORDIAMETER_MUDLINE(I)*0.0254)**2/4. !D(in), AREA(m^2) | |||||
ENDDO | |||||
!=========================================================================== | |||||
! MUDLINE PIPNING LOSSES INPUT | |||||
!=========================================================================== | |||||
MudSystem%NO_PIPINGSMUDLINE=4 | |||||
ALLOCATE (MudSystem%PIPINGS_MUDLINE(MudSystem%NO_PIPINGSMUDLINE,3)) | |||||
! ID(INCH) L(FEET) ROUGHNESS(MM)=e DESCRIPTION | |||||
MudSystem%PIPINGS_MUDLINE(1,1)= PumpsSpecification%MudPump1Output | |||||
MudSystem%PIPINGS_MUDLINE(1,2:3)= (/265., 0.03/) !(MLnumber=1,,PumpsToString) | |||||
MudSystem%PIPINGS_MUDLINE(2,1)= PumpsSpecification%MudPump1Output | |||||
MudSystem%PIPINGS_MUDLINE(2,2:3)= (/100., 0.03/) !(MLnumber=2,,STGaugeToString) | |||||
MudSystem%PIPINGS_MUDLINE(3,1:3)= (/0., 0., 0./) !(MLnumber=3,,WellToPits) | |||||
MudSystem%PIPINGS_MUDLINE(4,1)= BopStackSpecification%ChokeLineId | |||||
MudSystem%PIPINGS_MUDLINE(4,2)= BopStackSpecification%ChokeLineLength | |||||
MudSystem%PIPINGS_MUDLINE(4,3)= 0.03 !(MLnumber=4,,WellToChokeManifold) | |||||
MudSystem%Area_ChokeLineFt= PII*((BopStackSpecification%ChokeLineId/12.)**2)/4. !D(in), AREA(ft^2) | |||||
MudSystem%ChokeLine_VolumeCapacity= MudSystem%Area_ChokeLineFt* BopStackSpecification%ChokeLineLength* 7.48051948 ! (gal) | |||||
ALLOCATE (MudSystem%DIAM_MUDLINE_INCH(MudSystem%NO_PIPINGSMUDLINE), & | |||||
MudSystem%AREA_MUDLINE(MudSystem%NO_PIPINGSMUDLINE),MudSystem%LENGT_MUDLINE(MudSystem%NO_PIPINGSMUDLINE),MudSystem%ROUGHNESS_MUDLINE(MudSystem%NO_PIPINGSMUDLINE),MudSystem%RELROUGH_MUDLINE(MudSystem%NO_PIPINGSMUDLINE)) | |||||
DO I=1,MudSystem%NO_PIPINGSMUDLINE | |||||
MudSystem%DIAM_MUDLINE_INCH(I)=MudSystem%PIPINGS_MUDLINE(I,1) | |||||
MudSystem%LENGT_MUDLINE(I)=MudSystem%PIPINGS_MUDLINE(I,2) | |||||
MudSystem%ROUGHNESS_MUDLINE(I)=MudSystem%PIPINGS_MUDLINE(I,3) | |||||
MudSystem%AREA_MUDLINE(I)=PII*(MudSystem%DIAM_MUDLINE_INCH(I)*0.0254)**2/4 !D(in), AREA(m^2) | |||||
MudSystem%RELROUGH_MUDLINE(I)=MudSystem%ROUGHNESS_MUDLINE(I)/(MudSystem%DIAM_MUDLINE_INCH(I)*25.4) !e/D | |||||
!DIAM_MUDLINE_MM(I)=DIAM_MUDLINE_MM(I)*.001 ! (m) | |||||
MudSystem%LENGT_MUDLINE(I)=MudSystem%LENGT_MUDLINE(I)*.3048 ! (m) | |||||
ENDDO | |||||
!=========================================================================== | |||||
! MUDLINE STATIC LOSSES INPUT | |||||
!=========================================================================== | |||||
! Height are in (meter) | |||||
MudSystem%Pumps_Height= 0. | |||||
MudSystem%STpipeGauge_Height= 2. !(m) | |||||
MudSystem%Pits_Height= 1. !(m) | |||||
MudSystem%ChokeManifold_Height= 1.*0.3048 !(ft to meter) | |||||
MudSystem%WellChokeExit_Height= BopStackSpecification%GroundLevel-BopStackSpecification%KillHeight | |||||
END | |||||
SUBROUTINE MUDLINE_LOSSES(MLnumber) | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
integer I | |||||
INTEGER MLnumber | |||||
!===============================PIPE LOSS=================================== | |||||
MUD(MLnumber)%Re_MUDline=MUD(MLnumber)%Q*6.30902e-5*MudSystem%DIAM_MUDLINE_INCH(MLnumber)*0.0254/(MudSystem%AREA_MUDLINE(MLnumber)*MUD(MLnumber)%nu) !<<<<<< nu: DOROST SHAVAD.ALAN DAR STARTUP SET SHODE | |||||
!write(*,*) 'MUD(MLnumber)%Re_MUDline=' , MUD(MLnumber)%Re_MUDline | |||||
! Q*6.30902e-5 for (gpm) to (m^3/sec) | |||||
if ( MUD(MLnumber)%Re_MUDline<Re_cr) then | |||||
MUD(MLnumber)%fric=64/ MUD(MLnumber)%Re_MUDline | |||||
else | |||||
MUD(MLnumber)%fric=1/(-1.8*log10((MudSystem%RELROUGH_MUDLINE(MLnumber)/3.7)**1.11+6.9/ MUD(MLnumber)%Re_MUDline))**2 | |||||
endif | |||||
MUD(MLnumber)%fricloss=((MUD(MLnumber)%fric*(wdens*MUD(MLnumber)%Mud_SG*MudSystem%LENGT_MUDLINE(MLnumber)*(MUD(MLnumber)%Q*6.30902e-5/MudSystem%AREA_MUDLINE(MLnumber))**2))/(2*MudSystem%DIAM_MUDLINE_INCH(MLnumber)*0.0254))/6895 | |||||
!==============================MINOR LOSS=================================== | |||||
if (MudSystem%LF_MUDLINE(MLnumber)/=0) then | |||||
MUD(MLnumber)%minlosspa_MUDLINE=MudSystem%LF_MUDLINE(MLnumber)*wdens*MUD(MLnumber)%Mud_SG*(MUD(MLnumber)%Q*6.30902e-5/MudSystem%AREAMINOR_MUDLINE(MLnumber))**2/2 !(Pa) | |||||
MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi) | |||||
elseif (MudSystem%CV_MUDLINE(MLnumber)/=0) then | |||||
MUD(MLnumber)%minlosspa_MUDLINE=1000*MUD(MLnumber)%Mud_SG*((11.7*MUD(MLnumber)%Q*6.30902e-5*3600)/(MudSystem%CV_MUDLINE(MLnumber)))**2 !(pa) | |||||
MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi) | |||||
else | |||||
MUD(MLnumber)%minlosspa_MUDLINE=MudSystem%NOTE_MUDLINE(MLnumber)*1e5 !(pa) | |||||
MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi) | |||||
endif | |||||
!==========================STATIC & KINETIC LOSS============================= | |||||
MudSystem%String_Height= 50.*0.3048 !<<<<<<<<<<<<<<< (foot) to (meter). az khanom tarmigh | |||||
MUD(1)%static_loss=(MudSystem%String_Height- MudSystem%Pumps_Height)*0.0 !(MLnumber=1,,PumpsToString) | |||||
MUD(2)%static_loss=(MudSystem%String_Height- MudSystem%STpipeGauge_Height)*MUD(2)%Mud_SG*wdens*gravity/6895 ! (psi) (MLnumber=2,,STGaugeToString) | |||||
MUD(3)%static_loss=0. !(MLnumber=1,,WellToPits) | |||||
MUD(4)%static_loss=(MudSystem%ChokeManifold_Height- MudSystem%WellChokeExit_Height)*MUD(4)%Mud_SG*wdens*gravity/6895 !(MLnumber=4,,WellToChokeManifold) | |||||
! RAM(RNUMBER)%kinetic_loss1=MUD(MLnumber)%Mud_SG*MUD(MLnumber)%Mud_Density*(RAM(RNUMBER)%Q*6.30902e-5/((1/4.)*pi*(.72*0.254e-1)**2))**2/(2*6895) !(psi) | |||||
!============================TOTAL LOSS======================================= | |||||
MUD(MLnumber)%total_loss= MUD(MLnumber)%fricloss+ MUD(MLnumber)%minloss_MUDLINE+ MUD(MLnumber)%static_loss!+ RAM(RNUMBER)%kinetic_loss1 !(psi) | |||||
END | |||||
SUBROUTINE DEALLOCATE_ARRAYS_MudSystem() | |||||
USE MudSystemVARIABLES | |||||
implicit none | |||||
!=========================================================================== | |||||
! RAMLINE MINOR LOSSES INPUT | |||||
!=========================================================================== | |||||
if (allocated(MudSystem%MudMinors)) DEALLOCATE (MudSystem%MudMinors) | |||||
!=========================================================================== | |||||
! RAMLINE PIPNING LOSSES INPUT | |||||
!=========================================================================== | |||||
if (allocated(MudSystem%MINORDIAMETER_MUDLINE)) DEALLOCATE (MudSystem%MINORDIAMETER_MUDLINE) | |||||
if (allocated(MudSystem%AREAMINOR_MUDLINE)) DEALLOCATE (MudSystem%AREAMINOR_MUDLINE) | |||||
if (allocated(MudSystem%LF_MUDLINE)) DEALLOCATE (MudSystem%LF_MUDLINE) | |||||
if (allocated(MudSystem%CV_MUDLINE)) DEALLOCATE (MudSystem%CV_MUDLINE) | |||||
if (allocated(MudSystem%NOTE_MUDLINE)) DEALLOCATE (MudSystem%NOTE_MUDLINE) | |||||
!=========================================================================== | |||||
! ANNULAR MINOR LOSSES INPUT | |||||
!=========================================================================== | |||||
if (allocated(MudSystem%PIPINGS_MUDLINE)) DEALLOCATE (MudSystem%PIPINGS_MUDLINE) | |||||
!=========================================================================== | |||||
! ANNULAR PIPNING LOSSES INPUT | |||||
!=========================================================================== | |||||
if (allocated(MudSystem%DIAM_MUDLINE_INCH)) DEALLOCATE (MudSystem%DIAM_MUDLINE_INCH) | |||||
if (allocated(MudSystem%AREA_MUDLINE)) DEALLOCATE (MudSystem%AREA_MUDLINE) | |||||
if (allocated(MudSystem%LENGT_MUDLINE)) DEALLOCATE (MudSystem%LENGT_MUDLINE) | |||||
if (allocated(MudSystem%ROUGHNESS_MUDLINE)) DEALLOCATE (MudSystem%ROUGHNESS_MUDLINE) | |||||
if (allocated(MudSystem%RELROUGH_MUDLINE)) DEALLOCATE (MudSystem%RELROUGH_MUDLINE) | |||||
END | |||||
subroutine AddDynamicArray(array, value) | |||||
implicit none | |||||
REAL, allocatable, intent(inout) :: array(:) | |||||
REAL, intent(in) :: value | |||||
REAL, allocatable :: tempArr(:) | |||||
integer :: i, isize | |||||
!if(allocated(array)) then | |||||
! isize = size(array) | |||||
! allocate(tempArr(isize+1)) | |||||
! do i=1,isize | |||||
! tempArr(i) = array(i) | |||||
! end do | |||||
! tempArr(isize+1) = value | |||||
! deallocate(array) | |||||
! call move_alloc(tempArr, array) | |||||
!else | |||||
! allocate(array(1)) | |||||
! array(1) = value | |||||
!end if | |||||
end subroutine |
@@ -0,0 +1,193 @@ | |||||
MODULE MudSystemVARIABLES | |||||
use DynamicDoubleArray | |||||
use DynamicIntegerArray | |||||
use CDownHoleVariables | |||||
use CBopControlPanelVariables | |||||
use CEquipmentsConstants | |||||
! ! use CSimulationVariables | |||||
use CAccumulatorVariables | |||||
use CBopStackVariables | |||||
use CChokeControlPanelVariables | |||||
use CStandPipeManifoldVariables | |||||
USE CReservoirVariables | |||||
IMPLICIT NONE | |||||
integer, parameter :: BlownThreshold = 10 | |||||
REAL:: SG=1.12,WDENS=1000,GRAVITY=9.81,RE_CR=2000!,NU=9e-6 | |||||
!specific gravity of liquid | |||||
!water density(kg/m^3) | |||||
PARAMETER PII=3.14159265 | |||||
integer imud | |||||
type::MudSystemType | |||||
! temporary varibales for solving pressure jerks -- 1399-11-09 | |||||
integer Pump1BlownCount, Pump2BlownCount, Pump3BlownCount | |||||
!integer Pump1BlownInTimeStep, Pump2BlownInTimeStep, Pump3BlownInTimeStep | |||||
!logical Pump1BlownStarted, Pump2BlownStarted, Pump3BlownStarted | |||||
!integer, parameter :: BlownThresholdInSecond = 5 | |||||
real(8) total_add,total_injected | |||||
real(8) DeltaWellCap,WellCapOld,AnnCapOld,DeltaAnnCap | |||||
!======================================================================== | |||||
! KICK VARIABLES | |||||
!======================================================================== | |||||
REAL(8) KickDeltaVinAnnulus, KickVolumeinAnnulus | |||||
REAL(8) Kick_Forehead_X,Kick_RemainedVolume_in_LastSection,BackheadX,KickDv,KickDx,MinKickDv,Old_KickBackHead_X,Kick_Density | |||||
INTEGER NewInfluxElementCreated,Kick_Forehead_section,MudSection,Op_KickLoc,Ann_KickLoc,FirstSetKickMigration,Old_KickBackHead_Section | |||||
Integer iLoc,ChokeLine_KickLoc,KickNumber,NewInfluxNumber,SoundGasThroughChoke | |||||
LOGICAL DrillingMode | |||||
!real(8) HZ_ADD | |||||
integer Flow_timeCounter,MudSys_timeCounter,FluidFlowCounter | |||||
!======================================================================== | |||||
! MUD CIRCULATION | |||||
!======================================================================== | |||||
REAL(8), ALLOCATABLE:: Xstart_PipeSection(:),Xend_PipeSection(:),PipeSection_VolumeCapacity(:),Area_PipeSectionFt(:),OD_PipeSectionInch(:),ID_PipeSectionInch(:),Angle_PipeSection(:) | |||||
REAL(8), ALLOCATABLE:: Xstart_OpSection(:),Xend_OpSection(:),Area_OpSectionFt(:),OD_OpSectionInch(:),ID_OpSectionInch(:),OpSection_VolumeCapacity(:),GeoTypeOp(:),Angle_OpSection(:) | |||||
REAL(8), ALLOCATABLE:: TDXstart_MudElementArray(:) , TDXend_MudElementArray(:) , TDDensity_MudElementArray(:) | |||||
INTEGER, ALLOCATABLE:: GeoType(:) | |||||
real(8) StMudVolumeSum,St_MudSaved_Density,St_Saved_MudDischarged_Volume,St_Saved_MudDischarged_Volume_Final,MudVolume_InjectedToBH,MudVolume_InjectedFromAnn | |||||
real BitMudDensity | |||||
REAL(8) xx,NewVolume,UtubeEmptyVolume,NewDensity, MudCircVerticalDepth,TrueMinValue | |||||
REAL DirectionCoef | |||||
INTEGER isection,OpSection,SuctionMud,NoStringMudElements,ImudCount,NoCasingMudElements,NoHorizontalMudElements,AddedElementsToString | |||||
Integer TDNoHorizontalMudElements, TDNoStringMudElements, TDNoCasingMudElements | |||||
Integer istring,icasing,NoPipeSections,FirstMudSet | |||||
INTEGER NoBottomHoleMudElements,NoStringMudElementsForPlot,F_StringIntervalCounts_Old | |||||
INTEGER FirstSetUtube1,FirstSetUtube2,FirstAdded,NewPipeFilling,Hz_MudOrKick_Utube,UtubeFilling,totalLength | |||||
REAL(8) DeltaVolumeOp,DeltaVTemp,OldPosition,StringFlowRate,StringFlowRateFinal,AnnulusFlowRateFinal,TD_RemoveVolume_Remained,DeltaVolumePipe,DeltaVolumeAnnulusCapacity | |||||
REAL AnnulusFlowRate,ChokeLineFlowRate | |||||
Logical:: UtubePossibility,MudIsChanged,AddedPipe,UtubeMode1Activated,UtubeMode2Activated,WellisNOTFull,ChokeLineNOTFull | |||||
Logical:: ShoeLost,ShoeFractured,Kickexpansion_DueToMudLost,LostInTripOutIsDone | |||||
Integer UGBOSuccessionCounter, UGBOSuccessionCounterOld | |||||
REAL(8) Area_ChokeLineFt, ChokeLine_VolumeCapacity,TotalAddedVolume,LackageMudVolumeAfterFilling, LackageMudVolume, NewInflux_Density | |||||
real(8) DensityMixTol,Hz_Density_Utube,CuttingDensityMixTol,Op_Kick_Saved_Volume,Op_MudSaved_Density,Op_KickSaved_Density,Op_Saved_MudDischarged_Volume,OpMudVolumeSum,Op_NeededVolume_ToFill | |||||
real(8) Choke_Kick_Saved_Volume,Choke_Saved_MudDischarged_Volume,Choke_KickSaved_Density,Choke_MudSaved_Density,ChokeMudVolumeSum | |||||
integer Saved_Op_MudOrKick,Saved_Ann_MudOrKick,Saved_Choke_MudOrKick | |||||
real(8) Choke_Saved_MudDischarged_Volume_Final,Choke_Kick_Saved_Volume_Final | |||||
real(8) Qlost,FormationLostPressure,ShoeMudPressure,ShoeLostCoef, ShoeMudViscosity, ShoeMudDensity ,OldAnnulusCapacity | |||||
logical:: Ann_to_Choke_2mud | |||||
real(8) AnnMudVolumeSum,Ann_MudSaved_Density,Ann_KickSaved_Density,Ann_Saved_MudDischarged_Volume,Ann_Kick_Saved_Volume,Ann_Saved_MudDischarged_Volume_Final, Ann_Kick_Saved_Volume_Final | |||||
type(DynamicDoubleArrayType) :: Hz_MudDischarged_Volume,Hz_Mud_Backhead_X,Hz_Mud_Forehead_X,Hz_Density,Hz_RemainedVolume_in_LastSection,Hz_EmptyVolume_inBackheadLocation, & | |||||
Op_MudDischarged_Volume,Op_Mud_Backhead_X,Op_Mud_Forehead_X,Op_Density,Op_RemainedVolume_in_LastSection,Op_EmptyVolume_inBackheadLocation | |||||
type(DynamicDoubleArrayType) :: ChokeLine_MudDischarged_Volume,ChokeLine_Mud_Backhead_X,ChokeLine_Mud_Forehead_X,ChokeLine_Density,ChokeLine_RemainedVolume_in_LastSection, & | |||||
ChokeLine_EmptyVolume_inBackheadLocation | |||||
type(DynamicDoubleArrayType) :: St_MudDischarged_Volume,St_Mud_Backhead_X,St_Mud_Forehead_X,St_Density,St_RemainedVolume_in_LastSection, & | |||||
St_EmptyVolume_inBackheadLocation,Ann_MudDischarged_Volume,Ann_Mud_Backhead_X,Ann_Mud_Forehead_X, & | |||||
Ann_Density,Ann_RemainedVolume_in_LastSection,Ann_EmptyVolume_inBackheadLocation | |||||
type(DynamicIntegerArrayType) :: St_Mud_Backhead_section,St_Mud_Forehead_section,Ann_Mud_Backhead_section,Ann_Mud_Forehead_section,MudGeoType,Hz_Mud_Backhead_section,Hz_Mud_Forehead_section, & | |||||
Op_Mud_Backhead_section,Op_Mud_Forehead_section,Hz_MudOrKick,St_MudOrKick,Ann_MudOrKick,Op_MudOrKick,ChokeLine_MudOrKick,MudTypeOp_MudElement,MudType_MudElement | |||||
type(DynamicIntegerArrayType) :: ChokeLine_Mud_Backhead_section,ChokeLine_Mud_Forehead_section,Ann_CuttingMud | |||||
type(DynamicDoubleArrayType) :: Xend_MudElement,Xstart_MudElement,Density_MudElement,PipeID_MudElement,PipeOD_MudElement,Angle_MudElement, & | |||||
Xstart_OpMudElement,Xend_OpMudElement,Density_OpMudElement,PipeID_OpMudElement,PipeOD_OpMudElement!,Angle_OpMudElement | |||||
type(DynamicDoubleArrayType) :: TVDstart_MudElement, TVDend_MudElement, TVDstart_OpMudElement, TVDend_OpMudElement | |||||
type(CFluid), allocatable :: StringMudElement(:), CasingMudElement(:) | |||||
real(8) PressureGauge75,PressureGauge76 | |||||
!======================================================================== | |||||
! MALFUNCTION VARIABLES | |||||
!======================================================================== | |||||
INTEGER StandPipeGauge1Malf, StandPipeGauge2Malf, StandPipePressure_DataDisplayMalf,StandPipePressureChokeMalf,DrillPipePressureMalf | |||||
integer TripTankPressure_DataDisplayMalf,PitGainLossGaugeMalf,ReturnMudFlowGaugeMalf,MudTanksVolumeGaugeMalf | |||||
!======================================================================== | |||||
! TRIP TANK VARIABLES | |||||
!======================================================================== | |||||
logical condition32Final,condition33Final,condition34Final | |||||
REAL(8) TripTank_Vol,TripTank_Dens,ReturnToTrip_Q,ActiveToTrip_Q,TripTankPump_Q,ReturnToTrip_Dens,ActiveToTrip_Dens,ReturnToTrip_deltaV,ActiveToTrip_deltaV | |||||
REAL(8) MassFlowRate_ReturnToTrip,MassFlowRate_ActiveToTrip,TripTankPump_deltaV,MassFlowRate_TripTankPump,NetMassFlux_tripTank | |||||
REAL(8) TripTank_MinVol_Allowded,TripTank_MaxVol_Allowded | |||||
!!====================================================================== | |||||
!! MUD VOLUME TOTALIZER | |||||
!!====================================================================== | |||||
REAL(8) RefrencePitVolume_DrillWatch ! for DrillWatch | |||||
REAL(8) MudTank1_vol,MudTank2_vol,MudTank3_vol,MudTank4_vol | |||||
REAL(8) MVT_MinVol_Allowded,MVT_MaxVol_Allowded,MudTanksVolume | |||||
REAL(8) PitGainLossZero,MVTCoarse,MVTFine,RefrencePitVolume,PitGainLossZero_Old,MVTCoarseKnob_Old,MVTFineKnob_Old | |||||
REAL(8) ActiveTankDensity,TripTankDensityCalc,SuctionDensity_Old,AnnulusSuctionDensity_Old,StringDensity_Old,ChokeLineDensity_Old,ChokeManifoldDumpVolume | |||||
LOGICAL FirstSet_Time | |||||
!!====================================================================== | |||||
!! MUD FLOW-FILL INDICATOR | |||||
!!====================================================================== | |||||
REAL(8) TotalStrokes1MFFI,TotalStrokes2MFFI,TotalStrokesPump1,TotalStrokesPump2,GraphTotalStrokes | |||||
REAL(8) PedalMeter,ReturnFlowRate,ReturnFlowPercent,MFFI_MinPercent_Allowded,MFFI_MaxPercent_Allowded | |||||
REAL(8) TotalFillStrokes1MFFI,TotalFillStrokes2MFFI,TotalFilledStrokesBy1MFFI,TotalFilledStrokesBy2MFFI,TotalFilledStrokesBy1and2MFFI | |||||
!============================================================================ | |||||
! MUD & ENVIRONMENT VARIABLES | |||||
!============================================================================ | |||||
INTEGER NO_MudMinors,NO_PIPINGSMUDLINE | |||||
REAL(8) Pumps_Height,String_Height,STpipeGauge_Height,Pits_Height,ChokeManifold_Height,WellChokeExit_Height | |||||
REAL(8) STGauge_Pressure,String_Input_Pressure,Well_Output_Pressure,Pressure_BeforeChokes,Pressure_AfterChokes | |||||
REAL(8) OpenArea32,OpenArea33,OpenArea34,OpenArea35,deltaPchoke,WellOutletDensity,ChokeOutletDensity | |||||
REAL Q_flow32,Q_flow33,Q_flow34,Q_flow35 | |||||
REAL(8) DeltaT_Mudline,ActiveTankVolume,ReserveTankVolume,CementTankVolumeCalc,ActiveTankSettled,ActiveTankFloorArea,TripTankFloorArea | |||||
REAL(8) TripTankVolumeCalc,BellNippleDensity,BellNippleVolume,MudBucketDensity,MudBucketVolume,BellNippleDumpVolume | |||||
REAL(8) ReserveTankDensity,CementTankDensityCalc,Mp1Density,Mp2Density,Mp3Density,PumpsDumpVolume | |||||
real PumpsDumpFlowRate | |||||
REAL(8) Density_Ch | |||||
real(8) Suction_Density_MudSystem,Suction_Density_PumpsToWell,CompressedMudDensity | |||||
Logical WellToPitsOpen,WellToChokeManifoldOpen,MudChecked,WellHeadIsOpen | |||||
logical Pump1OffFailure,Pump2OffFailure,Pump3OffFailure,ChokeLineGaugeToTanks,WellToChokeLineGauge | |||||
REAL,ALLOCATABLE:: MudMinors(:,:),AREA_MUDLINE(:),MINORDIAMETER_MUDLINE(:),NOTE_MUDLINE(:),AREAMINOR_MUDLINE(:),LF_MUDLINE(:),CV_MUDLINE(:) | |||||
REAL,ALLOCATABLE:: DIAM_MUDLINE_INCH(:),LENGT_MUDLINE(:),ROUGHNESS_MUDLINE(:),RELROUGH_MUDLINE(:),PIPINGS_MUDLINE(:,:) | |||||
end type MudSystemType | |||||
type(MudSystemType)::MudSystem | |||||
TYPE, PUBLIC :: MUD_TypeVars | |||||
REAL Q,nu,Mud_Density,Mud_SG | |||||
REAL minlosspa_MUDLINE,minloss_MUDLINE ! MINORS | |||||
REAL Re_MUDline,fric,fricloss,static_loss,total_loss ! MUDLINE | |||||
END TYPE MUD_TypeVars | |||||
TYPE(MUD_TypeVars), DIMENSION(1:10) :: MUD | |||||
!MUD(1)%Q : ------------- | |||||
!MUD(2)%Q : PumpsToString | |||||
!MUD(3)%Q : BellNippleToPits-FullWell | |||||
!MUD(4)%Q : WellToChokeManifold | |||||
!MUD(5)%Q : ActiveTankToTripTank | |||||
!MUD(6)%Q : TripTankToActiveTank | |||||
!MUD(7)%Q : WellToBellNipple | |||||
!MUD(8)%Q : BellNippleToWell-NonFullWell | |||||
!MUD(9)%Q : StandPipeManifoldToChokeManifold-Through ChokeLine | |||||
!MUD(10)%Q : PumpsToWell_KillLine | |||||
! TYPE, PUBLIC :: MUD_TypeVars2D | |||||
! !! MINORS | |||||
! !REAL,ALLOCATABLE:: minlosspa_MUDLINE(:,:),minloss_MUDLINE(:,:) | |||||
! !! MUDLINE | |||||
! !REAL,ALLOCATABLE:: Re_MUDline(:,:),fric(:,:),fricloss(:,:) | |||||
! END TYPE MUD_TypeVars2D | |||||
! TYPE(MUD_TypeVars2D) :: MUDS | |||||
END MODULE | |||||
@@ -0,0 +1,410 @@ | |||||
subroutine PlotFinalMudElements ! is called in subroutine CirculationCodeSelect | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
Use TD_StringConnectionData | |||||
!USE CHOKEVARIABLES | |||||
!USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure | |||||
!use CManifolds | |||||
use CDrillWatchVariables | |||||
!use CHOKEVARIABLES | |||||
!use CChokeManifoldVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
USE sROP_Other_Variables | |||||
USE sROP_Variables | |||||
use KickVARIABLESModule | |||||
USE CKellyConnectionEnumVariables | |||||
use UTUBEVARSModule | |||||
use CLog1 | |||||
Use CError | |||||
Use , intrinsic :: IEEE_Arithmetic | |||||
implicit none | |||||
integer jelement, jmud, jsection,ielement,i | |||||
integer jopelement,jopmud,jopsection | |||||
character(len=120) :: temp1, temp2 | |||||
if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then | |||||
write(*,*) 'well cap=' , sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) | |||||
MudSystem%DeltaWellCap= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) - MudSystem%WellCapOld | |||||
MudSystem%WellCapOld= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) | |||||
write(*,*) 'cap_reset,DeltaWellCap=' , MudSystem%DeltaWellCap | |||||
endif | |||||
!========================ANNULUS END================= | |||||
if ((MudSystem%Ann_Mud_Forehead_X%Last() - BopStackSpecification%AboveAnnularHeight) > 0.8 .or. MudSystem%Ann_Density%Last()==0.0) then ! for Line (BellNippleToWell-NonFullWell) | |||||
MudSystem%WellisNOTFull= .true. | |||||
else | |||||
MudSystem%WellisNOTFull= .false. | |||||
endif | |||||
!WRITE(*,*) 'Ann_Mud_Forehead_X%Last() , KillHeight', Ann_Mud_Forehead_X%Last() , KillHeight | |||||
if ((MudSystem%Ann_Mud_Forehead_X%Last() - BopStackSpecification%KillHeight)>0.8 .or. MudSystem%Ann_Density%Last()==0.0) then ! for Line j4 , WellToChokeManifold(Through 26) | |||||
MudSystem%ChokeLineNOTFull= .true. | |||||
else | |||||
MudSystem%ChokeLineNOTFull= .false. | |||||
endif | |||||
!========================================================= | |||||
jmud= 1 | |||||
jsection= 1 | |||||
jelement= 0 ! number of final mud elements | |||||
call MudSystem%Xend_MudElement%Empty() | |||||
call MudSystem%TVDend_MudElement%Empty() | |||||
call MudSystem%Density_MudElement%Empty() | |||||
call MudSystem%MudGeoType%Empty() | |||||
call MudSystem%PipeID_MudElement%Empty() | |||||
call MudSystem%PipeOD_MudElement%Empty() | |||||
!call Angle_MudElement%Empty() | |||||
call MudSystem%MudType_MudElement%Empty() | |||||
DO WHILE(jmud <= MudSystem%Hz_Mud_Forehead_X%Length() .and. jsection<=1) | |||||
jelement= jelement+1 | |||||
MudSystem%TrueMinValue= min(MudSystem%Hz_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection)) | |||||
call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue) | |||||
call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%Density_MudElement%Add(MudSystem%Hz_Density%Array(jmud)) | |||||
call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection)) | |||||
call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection)) | |||||
!call Angle_MudElement%Add(Angle_PipeSection(jsection)) | |||||
call MudSystem%MudType_MudElement%Add(MudSystem%Hz_MudOrKick%Array(jmud)) | |||||
if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%Hz_Mud_Forehead_X%Array(jmud)) then | |||||
jmud= jmud+1 | |||||
else | |||||
jsection= jsection+1 | |||||
endif | |||||
ENDDO | |||||
MudSystem%NoHorizontalMudElements= jelement | |||||
jmud= 1 | |||||
jsection= 2 | |||||
DO WHILE(jmud <= MudSystem%St_Mud_Forehead_X%Length() .and. jsection<=F_Counts%StringIntervalCounts) | |||||
jelement= jelement+1 | |||||
MudSystem%TrueMinValue= min(MudSystem%St_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection)) | |||||
call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue) | |||||
call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%Density_MudElement%Add(MudSystem%St_Density%Array(jmud)) | |||||
call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection)) | |||||
call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection)) | |||||
!call Angle_MudElement%Add(Angle_PipeSection(jsection)) | |||||
call MudSystem%MudType_MudElement%Add(MudSystem%St_MudOrKick%Array(jmud)) | |||||
if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%St_Mud_Forehead_X%Array(jmud)) then | |||||
jmud= jmud+1 | |||||
else | |||||
jsection= jsection+1 | |||||
endif | |||||
ENDDO | |||||
MudSystem%NoStringMudElements= jelement- MudSystem%NoHorizontalMudElements | |||||
jmud= 1 | |||||
jsection= F_Counts%StringIntervalCounts+1 | |||||
DO WHILE(jmud<= MudSystem%Ann_Mud_Forehead_X%Length() .and. jsection<=MudSystem%NoPipeSections) | |||||
jelement= jelement+1 | |||||
MudSystem%TrueMinValue= max(MudSystem%Ann_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection)) | |||||
call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue) | |||||
call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%Density_MudElement%Add(MudSystem%Ann_Density%Array(jmud)) | |||||
call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection)) | |||||
call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection)) | |||||
!call Angle_MudElement%Add(Angle_PipeSection(jsection)) | |||||
call MudSystem%MudType_MudElement%Add(MudSystem%Ann_MudOrKick%Array(jmud)) | |||||
if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%Ann_Mud_Forehead_X%Array(jmud)) then | |||||
jmud= jmud+1 | |||||
else | |||||
jsection= jsection+1 | |||||
endif | |||||
ENDDO | |||||
do i= 2, MudSystem%Xend_MudElement%Length() | |||||
if ( i== MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+1) then | |||||
call MudSystem%Xstart_MudElement%Add (MudSystem%Ann_Mud_Backhead_X%Array(1)) ! start of annulus | |||||
call TVD_Calculator(MudSystem%Ann_Mud_Backhead_X%Array(1),MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDstart_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
elseif ( i== MudSystem%NoHorizontalMudElements+1 ) then | |||||
call MudSystem%Xstart_MudElement%Add (MudSystem%St_Mud_Backhead_X%Array(1)) ! start of stirng | |||||
call TVD_Calculator(MudSystem%St_Mud_Backhead_X%Array(1),MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDstart_MudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
else | |||||
call MudSystem%Xstart_MudElement%Add(MudSystem%Xend_MudElement%Array(i-1)) ! normal calculation | |||||
call MudSystem%TVDstart_MudElement%Add(MudSystem%TVDend_MudElement%Array(i-1)) ! normal calculation | |||||
endif | |||||
enddo | |||||
MudSystem%NoCasingMudElements = jelement- MudSystem%NoStringMudElements- MudSystem%NoHorizontalMudElements | |||||
!=========================For Torque and Drag======================== | |||||
if (allocated(MudSystem%TDXstart_MudElementArray)) deallocate(MudSystem%TDXstart_MudElementArray) | |||||
allocate(MudSystem%TDXstart_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements)) | |||||
if (allocated(MudSystem%TDXend_MudElementArray)) deallocate(MudSystem%TDXend_MudElementArray) | |||||
allocate(MudSystem%TDXend_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements)) | |||||
if (allocated(MudSystem%TDDensity_MudElementArray)) deallocate(MudSystem%TDDensity_MudElementArray) | |||||
allocate(MudSystem%TDDensity_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements)) | |||||
MudSystem%TDNoHorizontalMudElements= MudSystem%NoHorizontalMudElements | |||||
MudSystem%TDNoStringMudElements= MudSystem%NoStringMudElements | |||||
MudSystem%TDNoCasingMudElements= MudSystem%NoCasingMudElements | |||||
MudSystem%TDXstart_MudElementArray(:) = MudSystem%Xstart_MudElement%Array(:) | |||||
MudSystem%TDXend_MudElementArray(:) = MudSystem%Xend_MudElement%Array(:) | |||||
MudSystem%TDDensity_MudElementArray(:) = MudSystem%Density_MudElement%Array(:) | |||||
!===================================================================== | |||||
!do i=NoHorizontalMudElements+1, NoHorizontalMudElements+NoStringMudElements ! 2-string elements | |||||
! write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i) | |||||
!enddo | |||||
!================================================================ | |||||
! Open Hole Mud Elements | |||||
jopmud= 1 | |||||
jopsection= 1 | |||||
jopelement= 0 ! number of final mud elements | |||||
call MudSystem%Xend_OpMudElement%Empty() | |||||
call MudSystem%TVDend_OpMudElement%Empty() | |||||
call MudSystem%Density_OpMudElement%Empty() | |||||
call MudSystem%PipeID_OpMudElement%Empty() | |||||
call MudSystem%PipeOD_OpMudElement%Empty() | |||||
!call Angle_OpMudElement%Empty() | |||||
call MudSystem%MudTypeOp_MudElement%Empty() | |||||
DO WHILE(jopmud<= MudSystem%Op_Mud_Forehead_X%Length() .and. jopsection<=F_Counts%BottomHoleIntervalCounts) | |||||
jopelement= jopelement+1 | |||||
MudSystem%TrueMinValue= max(MudSystem%Op_Mud_Forehead_X%Array(jopmud), MudSystem%Xend_OpSection(jopsection)) | |||||
call MudSystem%Xend_OpMudElement%Add(MudSystem%TrueMinValue) | |||||
call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%TVDend_OpMudElement%Add(MudSystem%MudCircVerticalDepth) | |||||
call MudSystem%Density_OpMudElement%Add(MudSystem%Op_Density%Array(jopmud)) | |||||
call MudSystem%PipeID_OpMudElement%Add(MudSystem%ID_OpSectionInch(jopsection)) | |||||
call MudSystem%PipeOD_OpMudElement%Add(MudSystem%OD_OpSectionInch(jopsection)) | |||||
!call Angle_MudElement%Add(Angle_PipeSection(jopsection)) | |||||
call MudSystem%MudTypeOp_MudElement%Add(MudSystem%Op_MudOrKick%Array(jopmud)) | |||||
if (MudSystem%Xend_OpMudElement%Array(jopelement)== MudSystem%Op_Mud_Forehead_X%Array(jopmud)) then | |||||
jopmud= jopmud+1 | |||||
else | |||||
jopsection= jopsection+1 | |||||
endif | |||||
ENDDO | |||||
do i= 2, MudSystem%Xend_OpMudElement%Length() | |||||
call MudSystem%Xstart_OpMudElement%Add(MudSystem%Xend_OpMudElement%Array(i-1)) | |||||
call MudSystem%TVDstart_OpMudElement%Add(MudSystem%TVDend_OpMudElement%Array(i-1)) | |||||
enddo | |||||
MudSystem%NoBottomHoleMudElements = jopelement | |||||
!================================================================ | |||||
if(allocated(MudSystem%StringMudElement)) deallocate(MudSystem%StringMudElement) | |||||
allocate(MudSystem%StringMudElement(MudSystem%NoStringMudElements)) | |||||
if(allocated(MudSystem%CasingMudElement)) deallocate(MudSystem%CasingMudElement) | |||||
allocate(MudSystem%CasingMudElement(MudSystem%NoCasingMudElements+MudSystem%NoBottomHoleMudElements)) | |||||
MudSystem%istring=0 | |||||
MudSystem%icasing=0 | |||||
MudSystem%BitMudDensity= MudSystem%Density_MudElement%Array(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements) ! (for ROP module) | |||||
!================================================================ | |||||
!============================ UTUBE ============================= | |||||
!IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN | |||||
IF (MudSystem%UtubePossibility== .true. .and. TD_StConn%FluidStringConnectionMode==0 .and. MudSystem%WellHeadIsOpen .AND. NoGasPocket == 0) THEN | |||||
CALL WellPressureDataTransfer | |||||
!WRITE (*,*) ' U-Tube Done 1' | |||||
CALL Utube | |||||
!WRITE (*,*) ' U-Tube Done 2' | |||||
if (QUtubeInput> 0.0) call Utube1_and_TripIn | |||||
if (QUtubeOutput> 0.0) call Utube2_and_TripIn | |||||
END IF | |||||
!========================== UTUBE- end ========================= | |||||
! do imud=1, st_MudDischarged_Volume%Length() | |||||
! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud) | |||||
!enddo | |||||
!==================== Display ======================== | |||||
!do i=1, St_MudOrKick%Length() | |||||
! write(*,555) i,'St_Volume(i), type=' ,St_MudDischarged_Volume%Array(i),St_MudOrKick%Array(i) | |||||
! | |||||
! IF (IEEE_Is_NaN(St_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in St Volume-Plot') | |||||
! IF (St_MudDischarged_Volume%Array(i)<0.) call ErrorStop('St Volume <0' , St_MudDischarged_Volume%Array(i)) | |||||
!enddo | |||||
IF (ANY(IEEE_Is_NaN(MudSystem%Op_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystem%Op_MudDischarged_Volume%Array(:) <= 0.0)) THEN | |||||
do i = 1 , MudSystem%Op_MudOrKick%Length() | |||||
write(*,555) i,'Op_Volume(i), type=' ,MudSystem%Op_MudDischarged_Volume%Array(i) , MudSystem%Op_MudOrKick%Array(i) , MudSystem%Op_Density%Array(i) | |||||
end do | |||||
call ErrorStop('NaN in Op Volume-Plot or Op Volume <=0') | |||||
END IF | |||||
IF (ANY(IEEE_Is_NaN(MudSystem%Ann_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystem%Ann_MudDischarged_Volume%Array(:) <= 0.0)) THEN | |||||
do i = 1 , MudSystem%Ann_MudOrKick%Length() | |||||
write(*,555) i,'Ann_Volume(i), type=' ,MudSystem%Ann_MudDischarged_Volume%Array(i) , MudSystem%Ann_MudOrKick%Array(i) , MudSystem%Ann_Density%Array(i) | |||||
end do | |||||
call ErrorStop('NaN in Ann Volume-Plot or Ann Volume <=0') | |||||
END IF | |||||
!do i=1, Ann_MudOrKick%Length() | |||||
! !write(*,555) i,'Ann_Volume(i), type=' ,Ann_MudDischarged_Volume%Array(i),Ann_MudOrKick%Array(i),Ann_Density%Array(i) | |||||
! | |||||
! IF (IEEE_Is_NaN(Ann_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Ann Volume-Plot') | |||||
! IF (Ann_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Ann Volume <=0' , Ann_MudDischarged_Volume%Array(i)) | |||||
!enddo | |||||
555 FORMAT(I3,5X,A42,(f12.5),5X,I3,5X,(f12.5)) | |||||
MudSystem%NoStringMudElementsForPlot= MudSystem%NoStringMudElements | |||||
! 1-Horizontal Mud Elements are not shown | |||||
!write(*,333) 'Horiz:', 1,'Xstart\=', Xstart_MudElement%Array(1), 'Xend=' , Xend_MudElement%Array(1), 'Density=' , Density_MudElement%Array(1), 'MudType=' , MudType_MudElement%Array(1) | |||||
do i=MudSystem%NoHorizontalMudElements+1, MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements ! 2-string elements | |||||
if (MudSystem%Xend_MudElement%Array(i) <= 0.0) then | |||||
MudSystem%NoStringMudElementsForPlot= MudSystem%NoStringMudElementsForPlot-1 | |||||
cycle | |||||
endif | |||||
MudSystem%istring= MudSystem%istring+1 | |||||
MudSystem%StringMudElement(MudSystem%istring)%StartMd = MudSystem%Xstart_MudElement%Array(i) | |||||
MudSystem%StringMudElement(MudSystem%istring)%EndMd = MudSystem%Xend_MudElement%Array(i) | |||||
!StringMudElement(istring)%Id = PipeID_MudElement%Array(i) | |||||
!StringMudElement(istring)%Od = PipeOD_MudElement%Array(i) | |||||
MudSystem%StringMudElement(MudSystem%istring)%Density = MudSystem%Density_MudElement%Array(i) | |||||
if (MudSystem%MudType_MudElement%Array(i) == 104) then | |||||
MudSystem%MudType_MudElement%Array(i)= 4 ! air | |||||
elseif (MudSystem%MudType_MudElement%Array(i) > 0 .and. MudSystem%MudType_MudElement%Array(i) < 100) then ! all kicks | |||||
MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick | |||||
endif | |||||
MudSystem%StringMudElement(MudSystem%istring)%MudType = MudSystem%MudType_MudElement%Array(i) | |||||
!write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i) | |||||
enddo | |||||
do i=MudSystem%Xend_MudElement%Length(), MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+1 , -1 ! 3-casing elements | |||||
MudSystem%icasing= MudSystem%icasing+1 | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%StartMd = MudSystem%Xend_MudElement%Array(i) | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%EndMd = MudSystem%Xstart_MudElement%Array(i) | |||||
!CasingMudElement(icasing)%Id = PipeID_MudElement%Array(i) | |||||
!CasingMudElement(icasing)%Od = PipeOD_MudElement%Array(i) | |||||
!write(*,333) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i) | |||||
!call Log_1(temp1) | |||||
!write(*,444) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i) | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%Density = MudSystem%Density_MudElement%Array(i) | |||||
if (MudSystem%MudType_MudElement%Array(i) == 104) then | |||||
MudSystem%MudType_MudElement%Array(i)= 4 ! air | |||||
elseif (MudSystem%MudType_MudElement%Array(i) > 0 .and. MudSystem%MudType_MudElement%Array(i) < 100) then | |||||
MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick | |||||
endif | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%MudType = MudSystem%MudType_MudElement%Array(i) | |||||
enddo | |||||
do i= MudSystem%NoBottomHoleMudElements, 1 , -1 ! 4-open hole elements | |||||
MudSystem%icasing= MudSystem%icasing+1 | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%StartMd = MudSystem%Xend_OpMudElement%Array(i) | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%EndMd = MudSystem%Xstart_OpMudElement%Array(i) | |||||
!CasingMudElement(icasing)%Id = PipeID_OpMudElement%Array(i) | |||||
!CasingMudElement(icasing)%Od = PipeOD_OpMudElement%Array(i) | |||||
!write(*,333) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'Density=' , Density_OpMudElement%Array(i), 'MudType=' , MudTypeOp_MudElement%Array(i) | |||||
!call Log_1(temp2) | |||||
!write(*,444) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i) | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%Density = MudSystem%Density_OpMudElement%Array(i) | |||||
if (MudSystem%MudTypeOp_MudElement%Array(i) == 104) then | |||||
MudSystem%MudTypeOp_MudElement%Array(i)= 4 ! air | |||||
elseif (MudSystem%MudTypeOp_MudElement%Array(i) > 0 .and. MudSystem%MudTypeOp_MudElement%Array(i) < 100) then | |||||
MudSystem%MudTypeOp_MudElement%Array(i)= 1 ! gas kick | |||||
endif | |||||
MudSystem%CasingMudElement(MudSystem%icasing)%MudType = MudSystem%MudTypeOp_MudElement%Array(i) | |||||
enddo | |||||
333 FORMAT(A10,I3,5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,I3) | |||||
444 FORMAT(A10,I2,5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3)) | |||||
! shomare gozari be tartib HZ mud, ST mud, Casing | |||||
! shomare gzari OpenHole jodagane ast az 1 | |||||
call SetStringFluids(MudSystem%NoStringMudElementsForPlot, MudSystem%StringMudElement) !for data display in string | |||||
call SetAnnalusFluids(MudSystem%NoCasingMudElements+MudSystem%NoBottomHoleMudElements, MudSystem%CasingMudElement) !for data display in casing | |||||
!=========================================================================================================================== | |||||
!=========================================================================================================================== | |||||
end subroutine PlotFinalMudElements | |||||
@@ -0,0 +1,532 @@ | |||||
SUBROUTINE Utube1_and_TripIn ! is called in subroutine CirculationCodeSelect string to annulus | |||||
use UTUBEVARSModule | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
USE sROP_Variables | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
Use CShoeVariables | |||||
Use CUnityOutputs | |||||
implicit none | |||||
write(*,*) 'Utube1 code' | |||||
!===========================================================WELL============================================================ | |||||
!===========================================================WELL============================================================ | |||||
MudSystem%UtubeMode1Activated= .true. | |||||
!write(*,*) 'QUTubeInput=' , QUTubeInput | |||||
!Qinput=5000. | |||||
MudSystem%StringFlowRate= QUTubeInput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= QUTubeInput | |||||
MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | |||||
MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | |||||
!=========================================== | |||||
if (MudSystem%FirstSetUtube1==0) then | |||||
! call St_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval(1:F_StringIntervalCounts)%Volume))) !startup initial | |||||
! call St_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call St_Mud_Backhead_section%AddToFirst (1) | |||||
! call St_Mud_Forehead_X%AddToFirst (Xend_PipeSection(F_StringIntervalCounts)) | |||||
! call St_Mud_Forehead_section%AddToFirst (F_StringIntervalCounts) | |||||
! call MudSystem%St_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg) | |||||
! call St_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! | |||||
! call Ann_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval((F_StringIntervalCounts+F_BottomHoleIntervalCounts+1):F_IntervalsTotalCounts)%Volume))) !startup initial | |||||
! call Ann_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(F_StringIntervalCounts+1)) | |||||
! call Ann_Mud_Backhead_section%AddToFirst (F_StringIntervalCounts+1) | |||||
! call Ann_Mud_Forehead_X%AddToFirst (Xend_PipeSection(NoPipeSections)) | |||||
! call Ann_Mud_Forehead_section%AddToFirst (NoPipeSections) | |||||
! call Ann_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg) | |||||
! call Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
!Hz_Density%Array(:)= 0.0 !commented | |||||
!Hz_MudOrKick%Array(:)= 104 !commented | |||||
MudSystem%Hz_Density_Utube= 0.0 | |||||
MudSystem%Hz_MudOrKick_Utube= 104 | |||||
MudSystem%FirstSetUtube1= 1 | |||||
endif | |||||
!========================Horizontal PIPE ENTRANCE================= | |||||
!if (SuctionDensity_Old >= (ActiveDensity+0.05) .or. SuctionDensity_Old <= (ActiveDensity-0.05)) then ! new mud is pumped | |||||
! !ImudCount= ImudCount+1 | |||||
! !SuctionMud= ImudCount | |||||
! call Hz_Density%AddToFirst (REAL(ActiveDensity)) !ActiveDensity : badan in moteghayer bayad avaz beshe | |||||
! call Hz_MudDischarged_Volume%AddToFirst (0.0d0) | |||||
! call Hz_Mud_Forehead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call Hz_Mud_Forehead_section%AddToFirst (1) | |||||
! call Hz_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call Hz_Mud_Backhead_section%AddToFirst (1) | |||||
! call Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! call Hz_MudOrKick%AddToFirst (0) | |||||
! | |||||
! SuctionDensity_Old= ActiveDensity | |||||
!endif | |||||
!========================Horizontal PIPE STRING================= | |||||
!commented | |||||
! Hz_MudDischarged_Volume%Array(1)= Hz_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.)*DeltaT_Mudline) !(gal) | |||||
! | |||||
!imud=0 | |||||
! do while (imud < Hz_Mud_Forehead_X%Length()) | |||||
! imud = imud + 1 | |||||
! | |||||
! if (imud> 1) then | |||||
! Hz_Mud_Backhead_X%Array(imud)= Hz_Mud_Forehead_X%Array(imud-1) | |||||
! Hz_Mud_Backhead_section%Array(imud)= Hz_Mud_Forehead_section%Array(imud-1) | |||||
! endif | |||||
! | |||||
! | |||||
! DirectionCoef= (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud))) & | |||||
! / ABS(Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud))) | |||||
! ! +1 for string , -1 for annulus | |||||
! | |||||
! | |||||
! Hz_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))- Hz_Mud_Backhead_X%Array(imud))* & | |||||
! Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
! Hz_EmptyVolume_inBackheadLocation%Array(imud)= Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948 ! ft^3 to gal | |||||
! | |||||
! | |||||
! if ( Hz_MudDischarged_Volume%Array(imud) <= Hz_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
! Hz_Mud_Forehead_section%Array(imud)= Hz_Mud_Backhead_section%Array(imud) | |||||
! Hz_Mud_Forehead_X%Array(imud)= Hz_Mud_Backhead_X%Array(imud)+ DirectionCoef*(Hz_MudDischarged_Volume%Array(imud)/7.48051948)/Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud)) | |||||
! ! 7.48 is for gal to ft^3 | |||||
! else | |||||
! | |||||
! isection= Hz_Mud_Backhead_section%Array(imud)+1 | |||||
! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_EmptyVolume_inBackheadLocation%Array(imud) | |||||
! | |||||
! do | |||||
! if (isection > 1) then ! (horizontal pipe exit) | |||||
! Hz_MudDischarged_Volume%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_RemainedVolume_in_LastSection%Array(imud) | |||||
! Hz_Mud_Forehead_X%Array(imud)= Xend_PipeSection(1) | |||||
! Hz_Mud_Forehead_section%Array(imud)= 1 | |||||
! if (Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string | |||||
! call Hz_MudDischarged_Volume%Remove (imud) | |||||
! call Hz_Mud_Backhead_X%Remove (imud) | |||||
! call Hz_Mud_Backhead_section%Remove (imud) | |||||
! call Hz_Mud_Forehead_X%Remove (imud) | |||||
! call Hz_Mud_Forehead_section%Remove (imud) | |||||
! call Hz_Density%Remove (imud) | |||||
! call Hz_RemainedVolume_in_LastSection%Remove (imud) | |||||
! call Hz_EmptyVolume_inBackheadLocation%Remove (imud) | |||||
! call Hz_MudOrKick%Remove (imud) | |||||
! | |||||
! endif | |||||
! exit | |||||
! endif | |||||
! | |||||
! xx= Hz_RemainedVolume_in_LastSection%Array(imud)/ PipeSection_VolumeCapacity(isection) !(gal) | |||||
! | |||||
! if (xx<= 1.0) then | |||||
! Hz_Mud_Forehead_section%Array(imud)= isection | |||||
! Hz_Mud_Forehead_X%Array(imud)= (xx * (Xend_PipeSection(isection)- Xstart_PipeSection(isection)))+ Xstart_PipeSection(isection) | |||||
! exit | |||||
! else | |||||
! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_RemainedVolume_in_LastSection%Array(imud)- PipeSection_VolumeCapacity(isection) | |||||
! isection= isection+ 1 | |||||
! | |||||
! | |||||
! endif | |||||
! | |||||
! enddo | |||||
! | |||||
! endif | |||||
! | |||||
! enddo | |||||
!commented | |||||
!========================Horizontal PIPE END================= | |||||
!========================STRING ENTRANCE================= | |||||
!write(*,*) 'a) MudSystem%St_Density%Length()=' , MudSystem%St_Density%Length() | |||||
if (ABS(MudSystem%St_Density%First() - MudSystem%Hz_Density_Utube) >= MudSystem%DensityMixTol) then ! new mud is pumped | |||||
call MudSystem%St_Density%AddToFirst (MudSystem%Hz_Density_Utube) | |||||
call MudSystem%St_MudDischarged_Volume%AddToFirst (0.0d0) | |||||
call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) | |||||
call MudSystem%St_Mud_Forehead_section%AddToFirst (2) | |||||
call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) | |||||
call MudSystem%St_Mud_Backhead_section%AddToFirst (2) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
call MudSystem%St_MudOrKick%AddToFirst (MudSystem%Hz_MudOrKick_Utube) ! Hz_MudOrKick%Last() = 104 | |||||
!StringDensity_Old= Hz_Density_Utube | |||||
endif | |||||
!write(*,*) 'b) MudSystem%St_Density%Length()=' , MudSystem%St_Density%Length() | |||||
!write(*,*) 'b) MudSystem%St_Density%Array(1)=' , MudSystem%St_Density%Array(1) | |||||
!write(*,*) 'b) St_MudOrKick%Array(1)=' , St_MudOrKick%Array(1) | |||||
!========================STRING================= | |||||
!WRITE (*,*) 'Utube1 MudSystem%StringFlowRate', MudSystem%StringFlowRate | |||||
MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.d0)*MudSystem%DeltaT_Mudline) !(gal) | |||||
imud=0 | |||||
do while (imud < MudSystem%St_Mud_Forehead_X%Length()) | |||||
imud = imud + 1 | |||||
if (imud> 1) then | |||||
MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud-1) | |||||
MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud-1) | |||||
endif | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))- MudSystem%St_Mud_Backhead_X%Array(imud))* & | |||||
MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud) | |||||
MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%St_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%St_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) | |||||
! 7.48 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)+1 | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection > F_Counts%StringIntervalCounts) then ! last pipe section(string exit) F_Counts%StringIntervalCounts includes Horizontal line | |||||
MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts) | |||||
MudSystem%St_Mud_Forehead_section%Array(imud)= F_Counts%StringIntervalCounts | |||||
if (MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string | |||||
call RemoveStringMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%St_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection+ 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
enddo | |||||
!========================STRING END================= | |||||
!========================== tripping in for OP remove =============================== | |||||
!if (DeltaVolumeOp>0. .and. DeltaVolumeOp< Op_MudDischarged_Volume%Last()) then | |||||
! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length())= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()) - DeltaVolumeOp | |||||
!else | |||||
! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1)= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1) - (DeltaVolumeOp-Op_MudDischarged_Volume%Last()) | |||||
! | |||||
! call Op_MudDischarged_Volume%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Backhead_X%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Backhead_section%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Forehead_X%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Forehead_section%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Density%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_RemainedVolume_in_LastSection%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_EmptyVolume_inBackheadLocation%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_MudOrKick%Remove (Op_MudDischarged_Volume%Length()) | |||||
!endif | |||||
! | |||||
!============================= Bottom Hole ============================== | |||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
imud=0 | |||||
do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | |||||
imud = imud + 1 | |||||
if (imud> 1) then | |||||
MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1) | |||||
MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1) | |||||
endif | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))- MudSystem%Op_Mud_Backhead_X%Array(imud))* & | |||||
MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud) | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Op_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Op_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) | |||||
! 7.48 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1 | |||||
MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit) | |||||
if( imud==1) MudSystem%KickDeltaVinAnnulus= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space | |||||
MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts) | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts | |||||
if (MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well | |||||
call RemoveOpMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection+ 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
if (MudSystem%Op_Mud_Forehead_X%Array(imud)== MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then | |||||
MudSystem%totalLength = MudSystem%Op_MudDischarged_Volume%Length() | |||||
do while(imud < MudSystem%totalLength) | |||||
!imud = imud + 1 | |||||
call RemoveOpMudArrays(MudSystem%totalLength) | |||||
MudSystem%totalLength = MudSystem%totalLength - 1 | |||||
enddo | |||||
exit ! | |||||
endif | |||||
!WRITE(*,*) imud,'Op_MudDischarged_Volume%Array(imud)' , Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) | |||||
enddo | |||||
!write(*,*) 'Op_Mud_Forehead_X%Length()' , Op_Mud_Forehead_X%Length() | |||||
! | |||||
! WRITE(*,*) 'Xend_PipeSection(F_StringIntervalCounts)' , Xend_PipeSection(F_StringIntervalCounts) | |||||
! WRITE(*,*) 'Op_Mud_Backhead_X%Array(1)' , Op_Mud_Backhead_X%Array(1) | |||||
! WRITE(*,*) 'Op_Mud_Forehead_X%Array(1)' , Op_Mud_Forehead_X%Array(1) | |||||
! WRITE(*,*) 'Op_Mud_Backhead_X%Array(2)' , Op_Mud_Backhead_X%Array(2) | |||||
! WRITE(*,*) 'Op_Mud_Forehead_X%Array(2)' , Op_Mud_Forehead_X%Array(2) | |||||
!========================Bottom Hole END================= | |||||
if (MudSystem%iLoc == 1) then | |||||
MudSystem%MudSection= F_Counts%StringIntervalCounts+1 | |||||
MudSystem%BackheadX= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1) | |||||
elseif (MudSystem%iLoc == 2) then | |||||
MudSystem%MudSection= MudSystem%Kick_Forehead_section | |||||
MudSystem%BackheadX= MudSystem%Kick_Forehead_X | |||||
endif | |||||
!========================ANNULUS ENTRANCE==================== | |||||
!write(*,*) 'iloc=====' , iLoc | |||||
if ((ABS(MudSystem%AnnulusSuctionDensity_Old - MudSystem%St_Density%Last()) >= MudSystem%DensityMixTol) .OR. (MudSystem%DeltaVolumeOp == 0.0 .and. ABS(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%St_Density%Last())>=MudSystem%DensityMixTol .and. MudSystem%AnnulusFlowRate/=0.0d0) ) then ! new mud is pumped | |||||
call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%St_Density%Last()) | |||||
call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,0.0d0) | |||||
call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) | |||||
call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) | |||||
call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) | |||||
call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0) | |||||
call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0) | |||||
call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0) | |||||
MudSystem%AnnulusSuctionDensity_Old= MudSystem%St_Density%Last() | |||||
MudSystem%MudIsChanged= .true. | |||||
endif | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+ ((MudSystem%AnnulusFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) | |||||
!========================Tripping In==================== | |||||
!write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp | |||||
if (MudSystem%DeltaVolumeOp > 0.0 .and. MudSystem%MudIsChanged== .false.) then !.and. DrillingMode== .false.) then ! trip in mode(loole paeen) | |||||
!write(*,*) 'Tripping In' | |||||
MudSystem%NewDensity= (MudSystem%St_Density%Last()*((MudSystem%AnnulusFlowRate/60.)*MudSystem%DeltaT_Mudline)+MudSystem%Op_Density%Last()*MudSystem%DeltaVolumeOp)/(((MudSystem%AnnulusFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp) | |||||
MudSystem%NewVolume= ((MudSystem%AnnulusFlowRate/60.)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp | |||||
!write(*,*) 'Ann_MudDischarged_Volume%Array(1)=', Ann_MudDischarged_Volume%Array(1), 'NewVolume=', NewVolume | |||||
if (abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) then ! 1-Pockets are Merged - (ROP is 0) | |||||
MudSystem%Ann_Density%Array(MudSystem%iLoc)= (MudSystem%Ann_Density%Array(MudSystem%iLoc)*MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%DeltaVolumeOp | |||||
MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX | |||||
MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection | |||||
MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX | |||||
MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0) | |||||
else ! 2-Merging conditions are not meeted, so new pocket | |||||
call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity) | |||||
call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume) | |||||
call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) | |||||
call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) | |||||
call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) | |||||
call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0) | |||||
call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0) | |||||
call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0) | |||||
endif | |||||
elseif (MudSystem%DeltaVolumeOp > 0.0 .and. MudSystem%MudIsChanged== .true. .and. ROP_Bit%RateOfPenetration==0.) then | |||||
MudSystem%Ann_Density%Array(MudSystem%iLoc)= MudSystem%NewDensity | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%NewVolume | |||||
MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX | |||||
MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection | |||||
MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX | |||||
MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0) | |||||
endif | |||||
!========================Tripping In - End==================== | |||||
!======================== ANNULUS ==================== | |||||
MudSystem%MudIsChanged= .false. | |||||
imud= 0 | |||||
do while (imud < MudSystem%Ann_Mud_Forehead_X%Length()) | |||||
imud = imud + 1 | |||||
if (imud> 1) then | |||||
MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud-1) | |||||
MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud-1) | |||||
endif | |||||
! <<< Fracture Shoe Lost | |||||
IF ( MudSystem%ShoeLost .and. MudSystem%LostInTripOutIsDone== .false. .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then | |||||
!write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) | |||||
if (MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then | |||||
!write(*,*) 'mud is removed by shoe lost, imud=' , imud | |||||
call RemoveAnnulusMudArrays(imud) | |||||
imud= imud-1 | |||||
cycle | |||||
endif | |||||
ENDIF | |||||
! Fracture Shoe Lost >>> | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))- MudSystem%Ann_Mud_Backhead_X%Array(imud))* & | |||||
MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud) | |||||
MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Ann_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) | |||||
! 7.48 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%Ann_Mud_Backhead_section%Array(imud)+1 | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection > MudSystem%NoPipeSections) then ! last pipe section(well exit) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) | |||||
MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%NoPipeSections | |||||
if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well | |||||
call RemoveAnnulusMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%Ann_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection+ 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
enddo | |||||
!========================ANNULUS END================= | |||||
!if ( WellisNOTFull == .false. ) then | |||||
! write(*,*) 'MudSystem%AnnulusFlowRate==' , MudSystem%AnnulusFlowRate | |||||
! call Set_FlowRate(real(100.*min(MudSystem%AnnulusFlowRate,PedalMeter)/(PedalMeter/10.), 8)) | |||||
! | |||||
! | |||||
!endif | |||||
end subroutine Utube1_and_TripIn |
@@ -0,0 +1,517 @@ | |||||
SUBROUTINE Utube2_and_TripIn ! is called in subroutine CirculationCodeSelect annulus to string | |||||
use UTUBEVARSModule | |||||
Use GeoElements_FluidModule | |||||
USE CMudPropertiesVariables | |||||
USE MudSystemVARIABLES | |||||
USE Pumps_VARIABLES | |||||
use CDrillWatchVariables | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | |||||
Use CShoeVariables | |||||
implicit none | |||||
write(*,*) 'Utube2 code' | |||||
!===========================================================WELL============================================================ | |||||
!===========================================================WELL============================================================ | |||||
MudSystem%UtubeMode2Activated= .true. | |||||
write(*,*) 'QUtubeOutput=' , QUtubeOutput | |||||
!QUTubeInput=5000. | |||||
MudSystem%StringFlowRate= QUtubeOutput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= QUtubeOutput | |||||
MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | |||||
MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | |||||
!=========================================== | |||||
if (MudSystem%FirstSetUtube2==0) then | |||||
! call St_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval(1:F_StringIntervalCounts)%Volume))) !startup initial | |||||
! call St_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call St_Mud_Backhead_section%AddToFirst (1) | |||||
! call St_Mud_Forehead_X%AddToFirst (Xend_PipeSection(F_StringIntervalCounts)) | |||||
! call St_Mud_Forehead_section%AddToFirst (F_StringIntervalCounts) | |||||
! call MudSystem%St_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg) | |||||
! call St_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! | |||||
! call Ann_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval((F_StringIntervalCounts+F_BottomHoleIntervalCounts+1):F_IntervalsTotalCounts)%Volume))) !startup initial | |||||
! call Ann_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(F_StringIntervalCounts+1)) | |||||
! call Ann_Mud_Backhead_section%AddToFirst (F_StringIntervalCounts+1) | |||||
! call Ann_Mud_Forehead_X%AddToFirst (Xend_PipeSection(NoPipeSections)) | |||||
! call Ann_Mud_Forehead_section%AddToFirst (NoPipeSections) | |||||
! call Ann_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg) | |||||
! call Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
!Hz_Density%Array(:)= 0.0 | |||||
!Hz_MudOrKick%Array(:)= 104 | |||||
MudSystem%Hz_Density_Utube= 0.0 | |||||
MudSystem%Hz_MudOrKick_Utube= 104 | |||||
MudSystem%FirstSetUtube2= 1 | |||||
endif | |||||
!========================Horizontal PIPE ENTRANCE================= | |||||
!if (SuctionDensity_Old >= (ActiveDensity+0.05) .or. SuctionDensity_Old <= (ActiveDensity-0.05)) then ! new mud is pumped | |||||
! !ImudCount= ImudCount+1 | |||||
! !SuctionMud= ImudCount | |||||
! call Hz_Density%AddToFirst (REAL(ActiveDensity)) !ActiveDensity : badan in moteghayer bayad avaz beshe | |||||
! call Hz_MudDischarged_Volume%AddToFirst (0.0d0) | |||||
! call Hz_Mud_Forehead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call Hz_Mud_Forehead_section%AddToFirst (1) | |||||
! call Hz_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1)) | |||||
! call Hz_Mud_Backhead_section%AddToFirst (1) | |||||
! call Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0) | |||||
! call Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) | |||||
! call Hz_MudOrKick%AddToFirst (0) | |||||
! deltaV= 0. | |||||
! | |||||
! SuctionDensity_Old= ActiveDensity | |||||
!endif | |||||
!========================Horizontal PIPE STRING================= | |||||
!commented | |||||
! Hz_MudDischarged_Volume%Array(1)= Hz_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.)*DeltaT_Mudline) !(gal) | |||||
! | |||||
!imud=0 | |||||
! do while (imud < Hz_Mud_Forehead_X%Length()) | |||||
! imud = imud + 1 | |||||
! | |||||
! if (imud> 1) then | |||||
! Hz_Mud_Backhead_X%Array(imud)= Hz_Mud_Forehead_X%Array(imud-1) | |||||
! Hz_Mud_Backhead_section%Array(imud)= Hz_Mud_Forehead_section%Array(imud-1) | |||||
! endif | |||||
! | |||||
! | |||||
! DirectionCoef= (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud))) & | |||||
! / ABS(Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud))) | |||||
! ! +1 for string , -1 for annulus | |||||
! | |||||
! | |||||
! Hz_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))- Hz_Mud_Backhead_X%Array(imud))* & | |||||
! Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
! Hz_EmptyVolume_inBackheadLocation%Array(imud)= Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948 ! ft^3 to gal | |||||
! | |||||
! | |||||
! if ( Hz_MudDischarged_Volume%Array(imud) <= Hz_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
! Hz_Mud_Forehead_section%Array(imud)= Hz_Mud_Backhead_section%Array(imud) | |||||
! Hz_Mud_Forehead_X%Array(imud)= Hz_Mud_Backhead_X%Array(imud)+ DirectionCoef*(Hz_MudDischarged_Volume%Array(imud)/7.48051948)/Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud)) | |||||
! ! 7.48051948 is for gal to ft^3 | |||||
! else | |||||
! | |||||
! isection= Hz_Mud_Backhead_section%Array(imud)+1 | |||||
! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_EmptyVolume_inBackheadLocation%Array(imud) | |||||
! | |||||
! do | |||||
! if (isection > 1) then ! (horizontal pipe exit) | |||||
! Hz_MudDischarged_Volume%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_RemainedVolume_in_LastSection%Array(imud) | |||||
! Hz_Mud_Forehead_X%Array(imud)= Xend_PipeSection(1) | |||||
! Hz_Mud_Forehead_section%Array(imud)= 1 | |||||
! if (Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string | |||||
! call Hz_MudDischarged_Volume%Remove (imud) | |||||
! call Hz_Mud_Backhead_X%Remove (imud) | |||||
! call Hz_Mud_Backhead_section%Remove (imud) | |||||
! call Hz_Mud_Forehead_X%Remove (imud) | |||||
! call Hz_Mud_Forehead_section%Remove (imud) | |||||
! call Hz_Density%Remove (imud) | |||||
! call Hz_RemainedVolume_in_LastSection%Remove (imud) | |||||
! call Hz_EmptyVolume_inBackheadLocation%Remove (imud) | |||||
! call Hz_MudOrKick%Remove (imud) | |||||
! endif | |||||
! exit | |||||
! endif | |||||
! | |||||
! xx= Hz_RemainedVolume_in_LastSection%Array(imud)/ PipeSection_VolumeCapacity(isection) !(gal) | |||||
! | |||||
! if (xx<= 1.0) then | |||||
! Hz_Mud_Forehead_section%Array(imud)= isection | |||||
! Hz_Mud_Forehead_X%Array(imud)= (xx * (Xend_PipeSection(isection)- Xstart_PipeSection(isection)))+ Xstart_PipeSection(isection) | |||||
! exit | |||||
! else | |||||
! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_RemainedVolume_in_LastSection%Array(imud)- PipeSection_VolumeCapacity(isection) | |||||
! isection= isection+ 1 | |||||
! | |||||
! | |||||
! endif | |||||
! | |||||
! enddo | |||||
! | |||||
! endif | |||||
! | |||||
! enddo | |||||
!commented | |||||
!========================Horizontal PIPE END================= | |||||
!========================ANNULUS ENTRANCE==================== | |||||
if (ABS(MudSystem%AnnulusSuctionDensity_Old - MudSystem%Hz_Density_Utube) >= MudSystem%DensityMixTol ) then ! new mud is pumped | |||||
call MudSystem%Ann_Density%Add (MudSystem%Hz_Density_Utube) | |||||
call MudSystem%Ann_MudDischarged_Volume%Add (0.0d0) | |||||
call MudSystem%Ann_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)) | |||||
call MudSystem%Ann_Mud_Forehead_section%Add (MudSystem%NoPipeSections) | |||||
call MudSystem%Ann_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(MudSystem%NoPipeSections)) | |||||
call MudSystem%Ann_Mud_Backhead_section%Add (MudSystem%NoPipeSections) | |||||
call MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0) | |||||
call MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0) | |||||
call MudSystem%Ann_MudOrKick%Add (MudSystem%Hz_MudOrKick_Utube) ! Hz_MudOrKick%Last() = 104 | |||||
call MudSystem%Ann_CuttingMud%Add (0) | |||||
MudSystem%AnnulusSuctionDensity_Old= MudSystem%Hz_Density_Utube | |||||
endif | |||||
!========================ANNULUS==================== | |||||
MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Last()+ ((MudSystem%AnnulusFlowRate/60.)*MudSystem%DeltaT_Mudline) !(gal) | |||||
imud= MudSystem%Ann_Mud_Forehead_X%Length() + 1 | |||||
do while (imud > 1) | |||||
imud = imud - 1 | |||||
if (imud< MudSystem%Ann_Mud_Forehead_X%Length()) then | |||||
MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Ann_Mud_Backhead_X%Array(imud+1) | |||||
MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud+1) | |||||
endif | |||||
! <<< Fracture Shoe Lost | |||||
IF ( MudSystem%ShoeLost .and. MudSystem%LostInTripOutIsDone== .false. .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then | |||||
!write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline) | |||||
MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) | |||||
if (MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then | |||||
!write(*,*) 'mud is removed by shoe lost, imud=' , imud | |||||
call RemoveAnnulusMudArrays(imud) | |||||
imud= imud-1 | |||||
cycle | |||||
endif | |||||
ENDIF | |||||
! Fracture Shoe Lost >>> | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud)))* & | |||||
MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud)) !(ft^3) | |||||
MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud) | |||||
MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%DirectionCoef*(MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud)) | |||||
! 7.48051948 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%Ann_Mud_Forehead_section%Array(imud)-1 | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection < F_Counts%StringIntervalCounts+1) then ! last pipe section(well exit) F_Counts%StringIntervalCounts+1 is the first section in Annulus | |||||
MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1) | |||||
MudSystem%Ann_Mud_Backhead_section%Array(imud)= F_Counts%StringIntervalCounts+1 | |||||
if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well | |||||
call RemoveAnnulusMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%Ann_Mud_Backhead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xstart_PipeSection(MudSystem%isection)- MudSystem%Xend_PipeSection(MudSystem%isection)))+ MudSystem%Xend_PipeSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection- 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
enddo | |||||
!========================ANNULUS END================= | |||||
!========================== tripping in for OP remove =============================== | |||||
!if (DeltaVolumeOp>0. .and. DeltaVolumeOp< Op_MudDischarged_Volume%Last()) then | |||||
! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length())= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()) - DeltaVolumeOp | |||||
!else | |||||
! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1)= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1) - (DeltaVolumeOp-Op_MudDischarged_Volume%Last()) | |||||
! | |||||
! call Op_MudDischarged_Volume%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Backhead_X%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Backhead_section%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Forehead_X%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Mud_Forehead_section%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_Density%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_RemainedVolume_in_LastSection%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_EmptyVolume_inBackheadLocation%Remove (Op_MudDischarged_Volume%Length()) | |||||
! call Op_MudOrKick%Remove (Op_MudDischarged_Volume%Length()) | |||||
!endif | |||||
! | |||||
!============================= Bottom Hole ============================== | |||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
imud=0 | |||||
do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | |||||
imud = imud + 1 | |||||
if (imud> 1) then | |||||
MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1) | |||||
MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1) | |||||
endif | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))- MudSystem%Op_Mud_Backhead_X%Array(imud))* & | |||||
MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud) | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Op_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Op_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) | |||||
! 7.48051948 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1 | |||||
MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit) | |||||
if( imud==1) MudSystem%KickDeltaVinAnnulus= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space | |||||
MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts) | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts | |||||
if (MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well | |||||
call RemoveOpMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection+ 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
if (MudSystem%Op_Mud_Forehead_X%Array(imud)== MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then | |||||
MudSystem%totalLength = MudSystem%Op_MudDischarged_Volume%Length() | |||||
do while(imud < MudSystem%totalLength) | |||||
!imud = imud + 1 | |||||
call RemoveOpMudArrays(MudSystem%totalLength) | |||||
MudSystem%totalLength = MudSystem%totalLength - 1 | |||||
enddo | |||||
exit ! | |||||
endif | |||||
!WRITE(*,*) imud,'Op_MudDischarged_Volume%Array(imud)' , Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) | |||||
enddo | |||||
!write(*,*) 'Op_Mud_Forehead_X%Length()' , Op_Mud_Forehead_X%Length() | |||||
! | |||||
! WRITE(*,*) 'Xend_PipeSection(F_StringIntervalCounts)' , Xend_PipeSection(F_StringIntervalCounts) | |||||
! WRITE(*,*) 'Op_Mud_Backhead_X%Array(1)' , Op_Mud_Backhead_X%Array(1) | |||||
! WRITE(*,*) 'Op_Mud_Forehead_X%Array(1)' , Op_Mud_Forehead_X%Array(1) | |||||
! WRITE(*,*) 'Op_Mud_Backhead_X%Array(2)' , Op_Mud_Backhead_X%Array(2) | |||||
! WRITE(*,*) 'Op_Mud_Forehead_X%Array(2)' , Op_Mud_Forehead_X%Array(2) | |||||
!========================Bottom Hole END================= | |||||
! NO KICK | |||||
!========================STRING ENTRANCE================= | |||||
if ((ABS(MudSystem%St_Density%Last() - MudSystem%Ann_Density%First()) >= MudSystem%DensityMixTol) .OR. (MudSystem%DeltaVolumeOp == 0.0 .and. MudSystem%St_Density%Last() /= MudSystem%Ann_Density%Array(1) .and. MudSystem%StringFlowRate/=0.0d0)) then ! new mud is pumped | |||||
!if ((ABS(StringDensity_Old - Ann_Density%First()) >= DensityMixTol) .OR. (DeltaVolumeOp == 0.0 .and. MudSystem%St_Density%Last() /= Ann_Density%Array(1) .and. MudSystem%StringFlowRate/=0.0d0)) then ! new mud is pumped | |||||
call MudSystem%St_Density%Add (MudSystem%Ann_Density%First()) | |||||
call MudSystem%St_MudDischarged_Volume%Add (0.0d0) | |||||
call MudSystem%St_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)) | |||||
call MudSystem%St_Mud_Forehead_section%Add (F_Counts%StringIntervalCounts) | |||||
call MudSystem%St_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts)) | |||||
call MudSystem%St_Mud_Backhead_section%Add (F_Counts%StringIntervalCounts) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Add (0.0d0) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Add (0.0d0) | |||||
call MudSystem%St_MudOrKick%Add (0) | |||||
!StringDensity_Old= Ann_Density%First() | |||||
MudSystem%MudIsChanged= .true. | |||||
endif | |||||
MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_MudDischarged_Volume%Length())= MudSystem%St_MudDischarged_Volume%Last()+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) | |||||
!========================Tripping In==================== | |||||
!write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp | |||||
write(*,*) 'DeltaVolumeOp=' , MudSystem%DeltaVolumeOp | |||||
if (MudSystem%DeltaVolumeOp > 0.0 .and. MudSystem%MudIsChanged== .false.) then !.and. DrillingMode== .false.) then ! trip in mode(loole paeen) | |||||
!write(*,*) 'Tripping In' | |||||
MudSystem%NewDensity= (MudSystem%Ann_Density%First()*((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%Op_Density%Last()*MudSystem%DeltaVolumeOp)/(((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp) | |||||
MudSystem%NewVolume= ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp | |||||
!write(*,*) 'St_MudDischarged_Volume%Last()=', St_MudDischarged_Volume%Last(), 'NewVolume=', NewVolume | |||||
if (abs(MudSystem%St_Density%Last()-MudSystem%NewDensity)< MudSystem%DensityMixTol) then ! .OR. (St_MudDischarged_Volume%Last()< 42.) ) then !+ NewVolume)< 42.) then ! 1-Pockets are Merged | |||||
MudSystem%St_Density%Array(MudSystem%St_Density%Length())= (MudSystem%St_Density%Last()*MudSystem%St_MudDischarged_Volume%Last()+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%St_MudDischarged_Volume%Last()+MudSystem%NewVolume) | |||||
MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_Density%Length())= MudSystem%St_MudDischarged_Volume%Last()+MudSystem%DeltaVolumeOp | |||||
MudSystem%St_Mud_Forehead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)) | |||||
MudSystem%St_Mud_Forehead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts) | |||||
MudSystem%St_Mud_Backhead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts)) | |||||
MudSystem%St_Mud_Backhead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts) | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(MudSystem%St_Density%Length())= (0.0d0) | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(MudSystem%St_Density%Length())= (0.0d0) | |||||
else ! 2-Merging conditions are not meeted, so new pocket | |||||
call MudSystem%St_Density%Add (MudSystem%NewDensity) | |||||
call MudSystem%St_MudDischarged_Volume%Add (MudSystem%NewVolume) | |||||
call MudSystem%St_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)) | |||||
call MudSystem%St_Mud_Forehead_section%Add (F_Counts%StringIntervalCounts) | |||||
call MudSystem%St_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts)) | |||||
call MudSystem%St_Mud_Backhead_section%Add (F_Counts%StringIntervalCounts) | |||||
call MudSystem%St_RemainedVolume_in_LastSection%Add (0.0d0) | |||||
call MudSystem%St_EmptyVolume_inBackheadLocation%Add (0.0d0) | |||||
call MudSystem%St_MudOrKick%Add (0) | |||||
endif | |||||
elseif (MudSystem%DeltaVolumeOp > 0.0 .and. MudSystem%MudIsChanged== .true.) then | |||||
MudSystem%St_Density%Array(MudSystem%St_Density%Length())= MudSystem%NewDensity | |||||
MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_Density%Length())= MudSystem%NewVolume | |||||
MudSystem%St_Mud_Forehead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)) | |||||
MudSystem%St_Mud_Forehead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts) | |||||
MudSystem%St_Mud_Backhead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts)) | |||||
MudSystem%St_Mud_Backhead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts) | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(MudSystem%St_Density%Length())= (0.0d0) | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(MudSystem%St_Density%Length())= (0.0d0) | |||||
endif | |||||
!========================Tripping In - End==================== | |||||
!======================== STRING ==================== | |||||
MudSystem%MudIsChanged= .false. | |||||
imud= MudSystem%St_Mud_Forehead_X%Length() + 1 | |||||
do while (imud > 1) | |||||
imud = imud - 1 | |||||
if (imud< MudSystem%St_Mud_Forehead_X%Length()) then | |||||
MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%St_Mud_Backhead_X%Array(imud+1) | |||||
MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud+1) | |||||
endif | |||||
MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))) & | |||||
/ ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))) | |||||
! +1 for string , -1 for annulus | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%St_Mud_Forehead_X%Array(imud)- MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud)))* & | |||||
MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3) | |||||
MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal | |||||
if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then | |||||
MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud) | |||||
MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud)- MudSystem%DirectionCoef*(MudSystem%St_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Forehead_section%Array(imud)) | |||||
! 7.48051948 is for gal to ft^3 | |||||
else | |||||
MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)-1 | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud) | |||||
do | |||||
if (MudSystem%isection < 1) then ! last pipe section(string exit) | |||||
MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud) | |||||
MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%Xstart_PipeSection(2) | |||||
MudSystem%St_Mud_Backhead_section%Array(imud)= 2 | |||||
if (MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string | |||||
call RemoveStringMudArrays(imud) | |||||
endif | |||||
exit | |||||
endif | |||||
MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) | |||||
if (MudSystem%xx<= 1.0) then | |||||
MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%isection | |||||
MudSystem%St_Mud_Backhead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xstart_PipeSection(MudSystem%isection)- MudSystem%Xend_PipeSection(MudSystem%isection)))+ MudSystem%Xend_PipeSection(MudSystem%isection) | |||||
exit | |||||
else | |||||
MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) | |||||
MudSystem%isection= MudSystem%isection- 1 | |||||
endif | |||||
enddo | |||||
endif | |||||
enddo | |||||
!========================STRING END================= | |||||
end subroutine Utube2_and_TripIn |
@@ -1,14 +1,14 @@ | |||||
subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | Use MudSystemVARIABLES | ||||
USE TD_DrillStemComponents | USE TD_DrillStemComponents | ||||
Use CUnityInputs | Use CUnityInputs | ||||
Use CUnityOutputs | Use CUnityOutputs | ||||
USE CKellyConnectionEnumVariables | USE CKellyConnectionEnumVariables | ||||
USE UTUBEVARS | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | use sROP_Variables | ||||
USE PressureDisplayVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
@@ -53,7 +53,7 @@ subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | |||||
if (TD_Vol%RemoveVolume > 0.) call DisconnectingPipe !! .and. Get_JointConnectionPossible() == .false.) call DisconnectingPipe | if (TD_Vol%RemoveVolume > 0.) call DisconnectingPipe !! .and. Get_JointConnectionPossible() == .false.) call DisconnectingPipe | ||||
IF (KickFlux .AND. NOT(KickOffBottom)) THEN | |||||
IF (KickVARIABLES%KickFlux .AND. NOT(KickVARIABLES%KickOffBottom)) THEN | |||||
call Kick_Influx | call Kick_Influx | ||||
endif | endif | ||||
@@ -61,13 +61,12 @@ subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | |||||
IF ( MudSystem%NewInfluxNumber > 0 ) THEN | IF ( MudSystem%NewInfluxNumber > 0 ) THEN | ||||
!write(*,*) 'KickOffBottom , ROP=' , KickOffBottom , ROP_Bit%RateOfPenetration | |||||
call Kick_Migration | call Kick_Migration | ||||
endif | endif | ||||
! ============================ must be after migration ============================== | ! ============================ must be after migration ============================== | ||||
DO KickNumber= MudSystem%NewInfluxNumber-NoGasPocket+1 , MudSystem%NewInfluxNumber | |||||
DO KickNumber= MudSystem%NewInfluxNumber-KickVARIABLES%NoGasPocket+1 , MudSystem%NewInfluxNumber | |||||
! FINDING NEW KICK LOCATIONS: | ! FINDING NEW KICK LOCATIONS: | ||||
MudSystem%Ann_KickLoc= 0 | MudSystem%Ann_KickLoc= 0 | ||||
MudSystem%Op_KickLoc= 0 | MudSystem%Op_KickLoc= 0 | ||||
@@ -96,7 +95,7 @@ subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver | |||||
! ============================ must be after migration-end =========================== | ! ============================ must be after migration-end =========================== | ||||
IF (ALLOCATED(GasPocketWeight%Array) .and. KickNumber == MudSystem%NewInfluxNumber .AND. NOT(KickOffBottom) .AND. MudSystem%WellHeadIsOpen) THEN | |||||
IF (ALLOCATED(GasPocketWeight%Array) .and. KickNumber == MudSystem%NewInfluxNumber .AND. NOT(KickVARIABLES%KickOffBottom) .AND. MudSystem%WellHeadIsOpen) THEN | |||||
cycle | cycle | ||||
@@ -8,7 +8,7 @@ subroutine DisconnectingPipe ! is called in subroutine CirculationCodeSelect | |||||
! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
USE TD_DrillStemComponents | USE TD_DrillStemComponents | ||||
Use CKellyConnectionEnumVariables | Use CKellyConnectionEnumVariables | ||||
Use CUnityOutputs | Use CUnityOutputs | ||||
@@ -13,7 +13,7 @@ subroutine ElementsCreation ! is called in subroutine Fluid_Flow_Solver | |||||
! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ! !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
use CError | use CError | ||||
implicit none | implicit none | ||||
@@ -208,7 +208,7 @@ ALLOCATE (MudSystem%Xstart_OpSection(F_Counts%BottomHoleIntervalCounts),MudSyste | |||||
MudSystem%DeltaVolumePipe = INT(MudSystem%DeltaVolumePipe * 100000.d0) / 100000.d0 | MudSystem%DeltaVolumePipe = INT(MudSystem%DeltaVolumePipe * 100000.d0) / 100000.d0 | ||||
!DeltaVolumeAnnulusCapacity= ((Xend_PipeSection(F_Counts%StringIntervalCounts)-OldPosition))*Area_PipeSectionFt(NoPipeSections)* 7.48051948d0! ft^3 to gal | !DeltaVolumeAnnulusCapacity= ((Xend_PipeSection(F_Counts%StringIntervalCounts)-OldPosition))*Area_PipeSectionFt(NoPipeSections)* 7.48051948d0! ft^3 to gal | ||||
DrillStringSpeed = (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)-MudSystem%OldPosition) / 0.1 | |||||
KickVARIABLES%DrillStringSpeed = (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)-MudSystem%OldPosition) / 0.1 | |||||
MudSystem%DeltaVolumeAnnulusCapacity= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) - MudSystem%OldAnnulusCapacity | MudSystem%DeltaVolumeAnnulusCapacity= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) - MudSystem%OldAnnulusCapacity | ||||
@@ -11,7 +11,7 @@ subroutine FillingWell_By_BellNipple ! is called in subroutine CirculationCo | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
implicit none | implicit none | ||||
@@ -9,7 +9,7 @@ subroutine Kick_Expansion ! is called in subroutine CirculationCodeSelect | |||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
USE CReservoirVariables | USE CReservoirVariables | ||||
USE KickVARIABLES | |||||
use KickVARIABLESModule | |||||
implicit none | implicit none | ||||
@@ -132,7 +132,7 @@ subroutine Kick_Contraction ! is called in subroutine CirculationCodeSelect | |||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
USE CReservoirVariables | USE CReservoirVariables | ||||
USE KickVARIABLES | |||||
use KickVARIABLESModule | |||||
USE CError | USE CError | ||||
@@ -8,7 +8,7 @@ subroutine Kick_Influx ! is called in subroutine CirculationCodeSelect | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
implicit none | implicit none | ||||
@@ -42,7 +42,7 @@ subroutine Kick_Influx ! is called in subroutine CirculationCodeSelect | |||||
endif | endif | ||||
MudSystem%Op_MudDischarged_Volume%Array(1)= MudSystem%Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) due to KickFlux | |||||
MudSystem%Op_MudDischarged_Volume%Array(1)= MudSystem%Op_MudDischarged_Volume%Array(1)+ ((KickVARIABLES%GasKickPumpFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) due to KickFlux | |||||
!write(*,*) 'kick volume ok=' , Op_MudDischarged_Volume%Array(1) | !write(*,*) 'kick volume ok=' , Op_MudDischarged_Volume%Array(1) | ||||
@@ -61,13 +61,13 @@ subroutine Kick_Influx ! is called in subroutine CirculationCodeSelect | |||||
subroutine Instructor_CirculationMud_Edit ! is called in subroutine CirculationCodeSelect | subroutine Instructor_CirculationMud_Edit ! is called in subroutine CirculationCodeSelect | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | Use MudSystemVARIABLES | ||||
USE TD_DrillStemComponents | USE TD_DrillStemComponents | ||||
Use CUnityInputs | Use CUnityInputs | ||||
Use CUnityOutputs | Use CUnityOutputs | ||||
USE CKellyConnectionEnumVariables | USE CKellyConnectionEnumVariables | ||||
USE UTUBEVARS | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | use sROP_Variables | ||||
use sROP_Other_Variables | use sROP_Other_Variables | ||||
use CDownHoleVariables | use CDownHoleVariables | ||||
@@ -121,18 +121,18 @@ subroutine Instructor_CirculationMud_Edit ! is called in subroutine Circulat | |||||
subroutine ShoeLostSub ! is called in subroutine CirculationCodeSelect | subroutine ShoeLostSub ! is called in subroutine CirculationCodeSelect | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use MudSystemVARIABLES | Use MudSystemVARIABLES | ||||
USE TD_DrillStemComponents | USE TD_DrillStemComponents | ||||
Use CUnityInputs | Use CUnityInputs | ||||
Use CUnityOutputs | Use CUnityOutputs | ||||
USE CKellyConnectionEnumVariables | USE CKellyConnectionEnumVariables | ||||
USE UTUBEVARS | |||||
use UTUBEVARSModule | |||||
use sROP_Variables | use sROP_Variables | ||||
use sROP_Other_Variables | use sROP_Other_Variables | ||||
use CDownHoleVariables | use CDownHoleVariables | ||||
use CShoeVariables | use CShoeVariables | ||||
USE PressureDisplayVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
Use CWarningsVariables | Use CWarningsVariables | ||||
@@ -141,7 +141,7 @@ subroutine ShoeLostSub ! is called in subroutine CirculationCodeSelect | |||||
MudSystem%ShoeLost= .false. | MudSystem%ShoeLost= .false. | ||||
MudSystem%Kickexpansion_DueToMudLost= .false. | MudSystem%Kickexpansion_DueToMudLost= .false. | ||||
MudSystem%ShoeMudPressure= PressureGauges(5) | |||||
MudSystem%ShoeMudPressure= PressureDisplayVARIABLES%PressureGauges(5) | |||||
MudSystem%UGBOSuccessionCounter = MudSystem%UGBOSuccessionCounter + 1 | MudSystem%UGBOSuccessionCounter = MudSystem%UGBOSuccessionCounter + 1 | ||||
@@ -9,7 +9,7 @@ subroutine Kick_Migration ! is called in subroutine CirculationCodeSelect | |||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
USE CReservoirVariables | USE CReservoirVariables | ||||
USE KickVARIABLES | |||||
use KickVARIABLESModule | |||||
implicit none | implicit none | ||||
@@ -39,9 +39,9 @@ subroutine Kick_Migration ! is called in subroutine CirculationCodeSelect | |||||
!FirstSetKickMigration | !FirstSetKickMigration | ||||
!write(*,*) 'NewInfluxNumber=' , NewInfluxNumber | !write(*,*) 'NewInfluxNumber=' , NewInfluxNumber | ||||
DO KickNumber= MudSystem%NewInfluxNumber-NoGasPocket+1 , MudSystem%NewInfluxNumber | |||||
DO KickNumber= MudSystem%NewInfluxNumber-KickVARIABLES%NoGasPocket+1 , MudSystem%NewInfluxNumber | |||||
!write(*,*) 'KickNumber=' , KickNumber | !write(*,*) 'KickNumber=' , KickNumber | ||||
if (KickFlux .AND. NOT(KickOffBottom) .and. KickNumber == MudSystem%NewInfluxNumber) cycle | |||||
if (KickVARIABLES%KickFlux .AND. NOT(KickVARIABLES%KickOffBottom) .and. KickNumber == MudSystem%NewInfluxNumber) cycle | |||||
if ( KickNumber == MudSystem%Ann_MudOrKick%Last() ) cycle ! when the last element in Annulus is kick, Migration is not called | if ( KickNumber == MudSystem%Ann_MudOrKick%Last() ) cycle ! when the last element in Annulus is kick, Migration is not called | ||||
!write(*,*) 'Migration will be done for,KickNumber=' ,KickNumber | !write(*,*) 'Migration will be done for,KickNumber=' ,KickNumber | ||||
@@ -1,8 +1,8 @@ | |||||
module MudSystemModule | module MudSystemModule | ||||
USE MudSystemVARIABLES | USE MudSystemVARIABLES | ||||
USE PressureDisplayVARIABLES | |||||
USE FricPressDropVars | |||||
use PressureDisplayVARIABLESModule | |||||
USE FricPressDropVarsModule | |||||
USE Fluid_Flow_Startup_Vars | USE Fluid_Flow_Startup_Vars | ||||
USE CMudPropertiesVariables | USE CMudPropertiesVariables | ||||
USE CManifolds | USE CManifolds | ||||
@@ -631,7 +631,7 @@ module MudSystemModule | |||||
use CHOKEVARIABLES | use CHOKEVARIABLES | ||||
use CChokeManifoldVariables | use CChokeManifoldVariables | ||||
use CTanksVariables | use CTanksVariables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use CHoistingVariables | Use CHoistingVariables | ||||
! use CSimulationVariables | ! use CSimulationVariables | ||||
@@ -778,19 +778,19 @@ module MudSystemModule | |||||
!write(*,*) 'H83=' , H83 | !write(*,*) 'H83=' , H83 | ||||
!write(*,*) 'DumpPump2=' , DumpPump2 | !write(*,*) 'DumpPump2=' , DumpPump2 | ||||
!write(*,*) 'G83=' , G83 | !write(*,*) 'G83=' , G83 | ||||
PumpPressure1= jj2*(1-H82)*(1-DumpPump1)*G82* PressureGauges(1) | |||||
PumpPressure2= jj12*(1-H83)*(1-DumpPump2)*G83* PressureGauges(1) | |||||
PumpPressure3= jj13*(1-H84)*(1-DumpCementPump)*G84* PressureGauges(1) | |||||
PumpPressure1= jj2*(1-H82)*(1-DumpPump1)*G82* PressureDisplayVARIABLES%PressureGauges(1) | |||||
PumpPressure2= jj12*(1-H83)*(1-DumpPump2)*G83* PressureDisplayVARIABLES%PressureGauges(1) | |||||
PumpPressure3= jj13*(1-H84)*(1-DumpCementPump)*G84* PressureDisplayVARIABLES%PressureGauges(1) | |||||
! | ! | ||||
!write(*,*) 'jj2 , H82 , DumpPump1 , G82,PresCsureGauges(1)=' , jj2 , H82 , DumpPump1 , G82,PressureGauges(1) | !write(*,*) 'jj2 , H82 , DumpPump1 , G82,PresCsureGauges(1)=' , jj2 , H82 , DumpPump1 , G82,PressureGauges(1) | ||||
!write(*,*) '1)PumpPressure1=' , PumpPressure1 | !write(*,*) '1)PumpPressure1=' , PumpPressure1 | ||||
!write(*,*) 'PumpPressure2=' , PumpPressure2 | !write(*,*) 'PumpPressure2=' , PumpPressure2 | ||||
PumpToManifoldMudVol = 3.0 * 42.0 | |||||
FricPressDropVars%PumpToManifoldMudVol = 3.0 * 42.0 | |||||
!PumpToManifoldCompressedMudVol = PumpToManifoldCompressedMudVol + MP1_Q / ConvMinToSec * dt | !PumpToManifoldCompressedMudVol = PumpToManifoldCompressedMudVol + MP1_Q / ConvMinToSec * dt | ||||
!PumpToManifoldDeltaPDueToCompressibility = PumpToManifoldCompressedMudVol / (MudCompressibility * PumpToManifoldMudVol) | !PumpToManifoldDeltaPDueToCompressibility = PumpToManifoldCompressedMudVol / (MudCompressibility * PumpToManifoldMudVol) | ||||
IF(Mp1_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_82 .and. MP1_Q > 0.0) then | IF(Mp1_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_82 .and. MP1_Q > 0.0) then | ||||
PumpToManifoldCompressedMudVol = PumpToManifoldCompressedMudVol + MP1_Q / ConvMinToSec * dt | |||||
PumpPressure1= PumpToManifoldCompressedMudVol / (MudCompressibility * PumpToManifoldMudVol) | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol = FricPressDropVars%PumpToManifoldCompressedMudVol + MP1_Q / ConvMinToSec * dt | |||||
PumpPressure1= FricPressDropVars%PumpToManifoldCompressedMudVol / (MudCompressibility * FricPressDropVars%PumpToManifoldMudVol) | |||||
write(*,*) '21)PumpPressure1=' , PumpPressure1 | write(*,*) '21)PumpPressure1=' , PumpPressure1 | ||||
WRITE (*,*) ' valve 1 ', Manifold%Valve(1)%Status | WRITE (*,*) ' valve 1 ', Manifold%Valve(1)%Status | ||||
WRITE (*,*) ' valve 4 ', Manifold%Valve(4)%Status | WRITE (*,*) ' valve 4 ', Manifold%Valve(4)%Status | ||||
@@ -806,8 +806,8 @@ module MudSystemModule | |||||
ENDIF | ENDIF | ||||
IF(Mp2_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_83 .and. MP2_Q > 0.0 ) then | IF(Mp2_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_83 .and. MP2_Q > 0.0 ) then | ||||
PumpToManifoldCompressedMudVol = PumpToManifoldCompressedMudVol + MP2_Q / ConvMinToSec * dt | |||||
PumpPressure2= PumpToManifoldCompressedMudVol / (MudCompressibility * PumpToManifoldMudVol) | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol = FricPressDropVars%PumpToManifoldCompressedMudVol + MP2_Q / ConvMinToSec * dt | |||||
PumpPressure2= FricPressDropVars%PumpToManifoldCompressedMudVol / (MudCompressibility * FricPressDropVars%PumpToManifoldMudVol) | |||||
write(*,*) '22)PumpPressure1=' , PumpPressure2 | write(*,*) '22)PumpPressure1=' , PumpPressure2 | ||||
WRITE (*,*) ' -valve 1 ', Manifold%Valve(1)%Status | WRITE (*,*) ' -valve 1 ', Manifold%Valve(1)%Status | ||||
WRITE (*,*) ' -valve 4 ', Manifold%Valve(4)%Status | WRITE (*,*) ' -valve 4 ', Manifold%Valve(4)%Status | ||||
@@ -823,8 +823,8 @@ module MudSystemModule | |||||
ENDIF | ENDIF | ||||
IF(Cp_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_84 .AND. MP3_Q > 0.0 ) then | IF(Cp_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_84 .AND. MP3_Q > 0.0 ) then | ||||
PumpToManifoldCompressedMudVol = PumpToManifoldCompressedMudVol + MP3_Q / ConvMinToSec * dt | |||||
PumpPressure3= PumpToManifoldCompressedMudVol / (MudCompressibility * PumpToManifoldMudVol) | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol = FricPressDropVars%PumpToManifoldCompressedMudVol + MP3_Q / ConvMinToSec * dt | |||||
PumpPressure3= FricPressDropVars%PumpToManifoldCompressedMudVol / (MudCompressibility * FricPressDropVars%PumpToManifoldMudVol) | |||||
ENDIF | ENDIF | ||||
!***************************************************************************** | !***************************************************************************** | ||||
!if(((Mp1_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_82) .or. ( PumpPressure1 >= MaxWorkingPressure1 ) & | !if(((Mp1_NoPath == 1 .and. ThereIsPathFrom_71_72_73_To_82) .or. ( PumpPressure1 >= MaxWorkingPressure1 ) & | ||||
@@ -843,7 +843,7 @@ module MudSystemModule | |||||
if(PumpsSpecification%MudPump1ReliefValveIsSet .and. MudSystem%Pump1BlownCount >= BlownThreshold) then | if(PumpsSpecification%MudPump1ReliefValveIsSet .and. MudSystem%Pump1BlownCount >= BlownThreshold) then | ||||
write(*,*) 'valve 65 open, BLOWN' | write(*,*) 'valve 65 open, BLOWN' | ||||
call ChangeValve(65, .TRUE.) | call ChangeValve(65, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
MudSystem%Pump1BlownCount = 0 | MudSystem%Pump1BlownCount = 0 | ||||
!Pump1BlownStarted = .FALSE. | !Pump1BlownStarted = .FALSE. | ||||
!else | !else | ||||
@@ -871,7 +871,7 @@ module MudSystemModule | |||||
if (PumpsSpecification%MudPump2ReliefValveIsSet .and. MudSystem%Pump2BlownCount >= BlownThreshold) then | if (PumpsSpecification%MudPump2ReliefValveIsSet .and. MudSystem%Pump2BlownCount >= BlownThreshold) then | ||||
write(*,*) 'valve 66 open, BLOWN' | write(*,*) 'valve 66 open, BLOWN' | ||||
call ChangeValve(66, .TRUE.) | call ChangeValve(66, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
MudSystem%Pump2BlownCount = 0 | MudSystem%Pump2BlownCount = 0 | ||||
!Pump2BlownInTimeStep = 0 | !Pump2BlownInTimeStep = 0 | ||||
!Pump2BlownStarted = .FALSE. | !Pump2BlownStarted = .FALSE. | ||||
@@ -890,7 +890,7 @@ module MudSystemModule | |||||
if (PumpsSpecification%CementPumpReliefValveIsSet .and. MudSystem%Pump3BlownCount >= BlownThreshold) then | if (PumpsSpecification%CementPumpReliefValveIsSet .and. MudSystem%Pump3BlownCount >= BlownThreshold) then | ||||
!write(*,*) 'valve 67 open, BLOWN' | !write(*,*) 'valve 67 open, BLOWN' | ||||
call ChangeValve(67, .TRUE.) | call ChangeValve(67, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
MudSystem%Pump3BlownCount = 0 | MudSystem%Pump3BlownCount = 0 | ||||
!else | !else | ||||
! PumpPressure3= 6000. !psi | ! PumpPressure3= 6000. !psi | ||||
@@ -904,7 +904,7 @@ module MudSystemModule | |||||
MudSystem%Pump1BlownCount = MudSystem%Pump1BlownCount + 1 | MudSystem%Pump1BlownCount = MudSystem%Pump1BlownCount + 1 | ||||
if(MudSystem%Pump1BlownCount >= BlownThreshold) then | if(MudSystem%Pump1BlownCount >= BlownThreshold) then | ||||
call ChangeValve(65, .TRUE.) | call ChangeValve(65, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
call Activate_Pump1Failure() | call Activate_Pump1Failure() | ||||
MudSystem%Pump1OffFailure= .true. | MudSystem%Pump1OffFailure= .true. | ||||
MudSystem%Pump1BlownCount = 0 | MudSystem%Pump1BlownCount = 0 | ||||
@@ -918,7 +918,7 @@ module MudSystemModule | |||||
MudSystem%Pump2BlownCount = MudSystem%Pump2BlownCount + 1 | MudSystem%Pump2BlownCount = MudSystem%Pump2BlownCount + 1 | ||||
if(MudSystem%Pump2BlownCount >= BlownThreshold) then | if(MudSystem%Pump2BlownCount >= BlownThreshold) then | ||||
call ChangeValve(66, .TRUE.) | call ChangeValve(66, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
call Activate_Pump2Failure() | call Activate_Pump2Failure() | ||||
MudSystem%Pump2OffFailure= .true. | MudSystem%Pump2OffFailure= .true. | ||||
MudSystem%Pump2BlownCount = 0 | MudSystem%Pump2BlownCount = 0 | ||||
@@ -932,7 +932,7 @@ module MudSystemModule | |||||
MudSystem%Pump3BlownCount = MudSystem%Pump3BlownCount + 1 | MudSystem%Pump3BlownCount = MudSystem%Pump3BlownCount + 1 | ||||
if(MudSystem%Pump3BlownCount >= BlownThreshold) then | if(MudSystem%Pump3BlownCount >= BlownThreshold) then | ||||
call ChangeValve(67, .TRUE.) | call ChangeValve(67, .TRUE.) | ||||
PumpToManifoldCompressedMudVol= 0.0 | |||||
FricPressDropVars%PumpToManifoldCompressedMudVol= 0.0 | |||||
call Activate_Pump3Failure() | call Activate_Pump3Failure() | ||||
MudSystem%Pump3OffFailure= .true. | MudSystem%Pump3OffFailure= .true. | ||||
MudSystem%Pump3BlownCount = 0 | MudSystem%Pump3BlownCount = 0 | ||||
@@ -1571,7 +1571,7 @@ module MudSystemModule | |||||
if (K79 == 1) then | if (K79 == 1) then | ||||
MudSystem%PressureGauge75= PressureGauges(1) !String to Gauge75 | |||||
MudSystem%PressureGauge75= PressureDisplayVARIABLES%PressureGauges(1) !String to Gauge75 | |||||
elseif (K82 == 1 .and. k83 == 0 .and. k84 == 0 .and. k78 == 0) then | elseif (K82 == 1 .and. k83 == 0 .and. k84 == 0 .and. k78 == 0) then | ||||
MudSystem%PressureGauge75= PumpPressure1 | MudSystem%PressureGauge75= PumpPressure1 | ||||
@@ -1603,7 +1603,7 @@ module MudSystemModule | |||||
if (L79 == 1) then | if (L79 == 1) then | ||||
MudSystem%PressureGauge76= PressureGauges(1) !String to Gauge76 | |||||
MudSystem%PressureGauge76= PressureDisplayVARIABLES%PressureGauges(1) !String to Gauge76 | |||||
elseif (L82 == 1 .and. L83 == 0 .and. L84 == 0 .and. L78 == 0) then | elseif (L82 == 1 .and. L83 == 0 .and. L84 == 0 .and. L78 == 0) then | ||||
MudSystem%PressureGauge76= PumpPressure1 | MudSystem%PressureGauge76= PumpPressure1 | ||||
@@ -2221,16 +2221,29 @@ module MudSystemModule | |||||
if (StudentStation%PitGainLossZero) then | if (StudentStation%PitGainLossZero) then | ||||
DrillingWatch%PitGainLose= 0.d0 !DrillWatch | DrillingWatch%PitGainLose= 0.d0 !DrillWatch | ||||
MudSystem%RefrencePitVolume_DrillWatch= MudSystem%ActiveTankVolume/42. !(bbl) !DrillWatch | MudSystem%RefrencePitVolume_DrillWatch= MudSystem%ActiveTankVolume/42. !(bbl) !DrillWatch | ||||
!********************************************* | !********************************************* | ||||
DataDisplayConsole%PitGainLossGauge= 0. !MFF Indicator | DataDisplayConsole%PitGainLossGauge= 0. !MFF Indicator | ||||
MudSystem%RefrencePitVolume= MudSystem%ActiveTankVolume/42. !(bbl) !MFF Indicator | MudSystem%RefrencePitVolume= MudSystem%ActiveTankVolume/42. !(bbl) !MFF Indicator | ||||
endif | endif | ||||
!!====================================================================== | !!====================================================================== | ||||
!! MUD FLOW-FILL INDICATOR | !! MUD FLOW-FILL INDICATOR | ||||
!!====================================================================== | |||||
IF (DataDisplayConsole%MFFIPowerSwitch==1 ) THEN !.and. IsPortable==.false. | |||||
!!====================================================================== | |||||
IF (DataDisplayConsole%MFFIPowerSwitch==1 ) THEN !.and. IsPortable==.false. | |||||
!====================TotalStrokes Reset and Calculate====================== | !====================TotalStrokes Reset and Calculate====================== | ||||
if (DataDisplayConsole%MFFIResetTotalStrokes == 1) then | if (DataDisplayConsole%MFFIResetTotalStrokes == 1) then | ||||
IF (DataDisplayConsole%MFFIPumpSelectorSwitch == 1) THEN | IF (DataDisplayConsole%MFFIPumpSelectorSwitch == 1) THEN | ||||
@@ -2507,22 +2520,22 @@ module MudSystemModule | |||||
MudSystem%ReserveTankDensity= MudProperties%ReserveDensity ! update from student input | MudSystem%ReserveTankDensity= MudProperties%ReserveDensity ! update from student input | ||||
end subroutine | end subroutine | ||||
subroutine SetupMudSystem() | |||||
use CPathChangeEvents | |||||
use CMudPropertiesVariables | |||||
implicit none | |||||
! subroutine SetupMudSystem() | |||||
! use CPathChangeEvents | |||||
! use CMudPropertiesVariables | |||||
! implicit none | |||||
call BeforeTraverse%Add(InitialVarsBeforePathsChanges) | |||||
call AfterTraverse%Add(AfterPathsChanges) | |||||
call OnPathOpen%Add(WhenPathOpen) | |||||
! call BeforeTraverse%Add(InitialVarsBeforePathsChanges) | |||||
! call AfterTraverse%Add(AfterPathsChanges) | |||||
! call OnPathOpen%Add(WhenPathOpen) | |||||
call OnActiveMudVolumeChange%Add(ActiveMudVolumeChanged) | |||||
call OnActiveDensityChange%Add(ActiveDensityChanged) | |||||
call OnReserveMudVolumeChange%Add(ReserveMudVolumeChanged) | |||||
call OnReserveDensityChange%Add(ReserveDensityChanged) | |||||
! call OnActiveMudVolumeChange%Add(ActiveMudVolumeChanged) | |||||
! call OnActiveDensityChange%Add(ActiveDensityChanged) | |||||
! call OnReserveMudVolumeChange%Add(ReserveMudVolumeChanged) | |||||
! call OnReserveDensityChange%Add(ReserveDensityChanged) | |||||
end subroutine | |||||
! end subroutine | |||||
subroutine AfterPathsChanges() | subroutine AfterPathsChanges() | ||||
implicit none | implicit none | ||||
@@ -4,7 +4,7 @@ | |||||
use CTanksVariables | use CTanksVariables | ||||
USE CMudPropertiesVariables | USE CMudPropertiesVariables | ||||
Use GeoElements_FluidModule | Use GeoElements_FluidModule | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use CUnityOutputs | Use CUnityOutputs | ||||
Use CShoeVariables | Use CShoeVariables | ||||
USE Pumps_VARIABLES | USE Pumps_VARIABLES | ||||
@@ -82,7 +82,7 @@ MudSystem%FluidFlowCounter = 0 | |||||
!KickVolumeinAnnulus= 0.0 | !KickVolumeinAnnulus= 0.0 | ||||
MudSystem%KickDeltaVinAnnulus= 0.0 | MudSystem%KickDeltaVinAnnulus= 0.0 | ||||
GasKickPumpFlowRate= 0.0 | |||||
KickVARIABLES%GasKickPumpFlowRate= 0.0 | |||||
MudSystem%FirstMudSet= 0 | MudSystem%FirstMudSet= 0 | ||||
MudSystem%FirstSetUtube1=0 | MudSystem%FirstSetUtube1=0 | ||||
@@ -122,7 +122,7 @@ MudSystem%FluidFlowCounter = 0 | |||||
USE CBopStackVariables | USE CBopStackVariables | ||||
USE CPumpsVariables | USE CPumpsVariables | ||||
use CTanksVariables | use CTanksVariables | ||||
USE KickVariables | |||||
use KickVARIABLESModule | |||||
implicit none | implicit none | ||||
@@ -141,7 +141,7 @@ MudSystem%FluidFlowCounter = 0 | |||||
MudSystem%DeltaT_Mudline=0.1 !second | MudSystem%DeltaT_Mudline=0.1 !second | ||||
GasKickPumpFlowRate= 0. | |||||
KickVARIABLES%GasKickPumpFlowRate= 0. | |||||
MudSystem%BellNippleVolume= 0. | MudSystem%BellNippleVolume= 0. | ||||
MudSystem%BellNippleDensity= 0. | MudSystem%BellNippleDensity= 0. | ||||
MudSystem%MudBucketVolume= 0. | MudSystem%MudBucketVolume= 0. | ||||
@@ -14,9 +14,9 @@ subroutine PlotFinalMudElements ! is called in subroutine CirculationCodeSel | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
USE CKellyConnectionEnumVariables | USE CKellyConnectionEnumVariables | ||||
USE UTUBEVARS | |||||
use UTUBEVARSModule | |||||
use CLog1 | use CLog1 | ||||
Use CError | Use CError | ||||
Use , intrinsic :: IEEE_Arithmetic | Use , intrinsic :: IEEE_Arithmetic | ||||
@@ -269,13 +269,13 @@ endif | |||||
!============================ UTUBE ============================= | !============================ UTUBE ============================= | ||||
!IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN | !IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN | ||||
IF (MudSystem%UtubePossibility== .true. .and. TD_StConn%FluidStringConnectionMode==0 .and. MudSystem%WellHeadIsOpen .AND. NoGasPocket == 0) THEN | |||||
IF (MudSystem%UtubePossibility== .true. .and. TD_StConn%FluidStringConnectionMode==0 .and. MudSystem%WellHeadIsOpen .AND. KickVARIABLES%NoGasPocket == 0) THEN | |||||
CALL WellPressureDataTransfer | CALL WellPressureDataTransfer | ||||
!WRITE (*,*) ' U-Tube Done 1' | !WRITE (*,*) ' U-Tube Done 1' | ||||
CALL Utube | CALL Utube | ||||
!WRITE (*,*) ' U-Tube Done 2' | !WRITE (*,*) ' U-Tube Done 2' | ||||
if (QUtubeInput> 0.0) call Utube1_and_TripIn | |||||
if (QUtubeOutput> 0.0) call Utube2_and_TripIn | |||||
if (UTUBEVARS%QUtubeInput> 0.0) call Utube1_and_TripIn | |||||
if (UTUBEVARS%QUtubeOutput> 0.0) call Utube2_and_TripIn | |||||
END IF | END IF | ||||
!========================== UTUBE- end ========================= | !========================== UTUBE- end ========================= | ||||
@@ -13,7 +13,7 @@ subroutine Pump_and_TripIn ! is called in subroutine CirculationCodeSelect | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use CShoeVariables | Use CShoeVariables | ||||
use CError | use CError | ||||
@@ -410,7 +410,7 @@ imud=0 | |||||
if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then | if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then | ||||
if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the | |||||
if (KickVARIABLES%KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the | |||||
AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick | AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick | ||||
else | else | ||||
AddLocation= MudSystem%Op_Density%Length()+1 | AddLocation= MudSystem%Op_Density%Length()+1 | ||||
@@ -1183,8 +1183,8 @@ imud=0 | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
USE PressureDisplayVARIABLES | |||||
use KickVARIABLESModule | |||||
use PressureDisplayVARIABLESModule | |||||
Use CError | Use CError | ||||
Use , intrinsic :: IEEE_Arithmetic | Use , intrinsic :: IEEE_Arithmetic | ||||
@@ -1597,8 +1597,8 @@ use CSounds | |||||
!use CTanksVariables, TripTankVolume2 => TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
!USE sROP_Other_Variables | !USE sROP_Other_Variables | ||||
!USE sROP_Variables | !USE sROP_Variables | ||||
!Use KickVariables | |||||
!USE PressureDisplayVARIABLES | |||||
!use KickVARIABLESModule | |||||
!use PressureDisplayVARIABLESModule | |||||
!Use CError | !Use CError | ||||
!Use , intrinsic :: IEEE_Arithmetic | !Use , intrinsic :: IEEE_Arithmetic | ||||
@@ -13,7 +13,7 @@ subroutine TripOut_and_Pump ! is called in subroutine CirculationCodeSelect | |||||
!use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity | ||||
USE sROP_Other_Variables | USE sROP_Other_Variables | ||||
USE sROP_Variables | USE sROP_Variables | ||||
Use KickVariables | |||||
use KickVARIABLESModule | |||||
Use CShoeVariables | Use CShoeVariables | ||||
use CError | use CError | ||||
@@ -427,7 +427,7 @@ imud=0 | |||||
if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then | if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then | ||||
if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the | |||||
if (KickVARIABLES%KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the | |||||
AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick | AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick | ||||
else | else | ||||
AddLocation= MudSystem%Op_Density%Length()+1 | AddLocation= MudSystem%Op_Density%Length()+1 | ||||
@@ -1,6 +1,6 @@ | |||||
SUBROUTINE Utube1_and_TripIn ! is called in subroutine CirculationCodeSelect string to annulus | SUBROUTINE Utube1_and_TripIn ! is called in subroutine CirculationCodeSelect string to annulus | ||||
Use UTUBEVARS | |||||
use UTUBEVARSModule | |||||
Use GeoElements_FluidModule | Use GeoElements_FluidModule | ||||
USE CMudPropertiesVariables | USE CMudPropertiesVariables | ||||
USE MudSystemVARIABLES | USE MudSystemVARIABLES | ||||
@@ -19,8 +19,8 @@ SUBROUTINE Utube1_and_TripIn ! is called in subroutine CirculationCodeSelect | |||||
MudSystem%UtubeMode1Activated= .true. | MudSystem%UtubeMode1Activated= .true. | ||||
!write(*,*) 'QUTubeInput=' , QUTubeInput | !write(*,*) 'QUTubeInput=' , QUTubeInput | ||||
!Qinput=5000. | !Qinput=5000. | ||||
MudSystem%StringFlowRate= QUTubeInput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= QUTubeInput | |||||
MudSystem%StringFlowRate= UTUBEVARS%QUTubeInput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= UTUBEVARS%QUTubeInput | |||||
MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | ||||
MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | ||||
!=========================================== | !=========================================== | ||||
@@ -258,7 +258,7 @@ imud=0 | |||||
!============================= Bottom Hole ============================== | !============================= Bottom Hole ============================== | ||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((KickVARIABLES%GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
imud=0 | imud=0 | ||||
do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | ||||
imud = imud + 1 | imud = imud + 1 | ||||
@@ -1,6 +1,6 @@ | |||||
SUBROUTINE Utube2_and_TripIn ! is called in subroutine CirculationCodeSelect annulus to string | SUBROUTINE Utube2_and_TripIn ! is called in subroutine CirculationCodeSelect annulus to string | ||||
Use UTUBEVARS | |||||
use UTUBEVARSModule | |||||
Use GeoElements_FluidModule | Use GeoElements_FluidModule | ||||
USE CMudPropertiesVariables | USE CMudPropertiesVariables | ||||
USE MudSystemVARIABLES | USE MudSystemVARIABLES | ||||
@@ -17,10 +17,10 @@ SUBROUTINE Utube2_and_TripIn ! is called in subroutine CirculationCodeSelect | |||||
!===========================================================WELL============================================================ | !===========================================================WELL============================================================ | ||||
MudSystem%UtubeMode2Activated= .true. | MudSystem%UtubeMode2Activated= .true. | ||||
write(*,*) 'QUtubeOutput=' , QUtubeOutput | |||||
write(*,*) 'QUtubeOutput=' , UTUBEVARS%QUtubeOutput | |||||
!QUTubeInput=5000. | !QUTubeInput=5000. | ||||
MudSystem%StringFlowRate= QUtubeOutput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= QUtubeOutput | |||||
MudSystem%StringFlowRate= UTUBEVARS%QUtubeOutput ! (gpm) | |||||
MudSystem%AnnulusFlowRate= UTUBEVARS%QUtubeOutput | |||||
MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate | ||||
MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate | ||||
!=========================================== | !=========================================== | ||||
@@ -270,7 +270,7 @@ imud= MudSystem%Ann_Mud_Forehead_X%Length() + 1 | |||||
!============================= Bottom Hole ============================== | !============================= Bottom Hole ============================== | ||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
!Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((KickVARIABLES%GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux | |||||
imud=0 | imud=0 | ||||
do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) | ||||
imud = imud + 1 | imud = imud + 1 | ||||
@@ -0,0 +1,45 @@ | |||||
SUBROUTINE AnnulusPropertyCalculator (md, den, pre, tem) | |||||
!!! This subroutine gets location of a guage or an observation point and determines information of that point such as pressure, density, velocity and temperature later. | |||||
use PressureDisplayVARIABLESModule | |||||
USE Fluid_Flow_Startup_Vars | |||||
USE MudSystemVARIABLES | |||||
USE FricPressDropVarsModule | |||||
USE CDrillWatchVariables | |||||
IMPLICIT NONE | |||||
INTEGER, intent(in) :: md ! input | |||||
REAL(8) :: TVD | |||||
real(8), intent(inout) :: den ! output | |||||
real(8), intent(inout) :: pre ! output | |||||
real(8), intent(inout) :: tem ! output | |||||
INTEGER :: ilocal | |||||
CALL TVD_Calculator(md * 1.d0 , TVD) | |||||
IF (md <= INT(FinalFlowEl(AnnulusFirstEl)%StartX)) THEN !! mouse pointer is in the annulus space | |||||
DO ilocal = AnnulusFirstEl , AnnulusLastEl | |||||
IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT | |||||
END DO | |||||
ELSE IF (md > INT(FinalFlowEl(NumbEl)%EndX)) THEN ! mouse pointer is in the open hole space | |||||
DO ilocal = OpenholeFirstEl , NumbEl | |||||
IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT | |||||
END DO | |||||
ELSE | |||||
WRITE (*,*) ' Error in calculating annulus observation point ' | |||||
END IF | |||||
pre = FinalFlowEl(ilocal)%StartPress - (FinalFlowEl(ilocal)%StartX - md) * FinalFlowEl(ilocal)%dPdLfric & | |||||
- (FinalFlowEl(ilocal)%StartTVD - TVD) * FinalFlowEl(ilocal)%dPdLGrav | |||||
!write(*,*) ' md, ilocal', md, ilocal | |||||
!WRITE (*,*) ' FlowEl dPdLfric , dPdLGrav', FlowEl(ilocal)%dPdLfric , FlowEl(ilocal)%dPdLGrav | |||||
den = FinalFlowEl(ilocal)%Density | |||||
!tem = 500 | |||||
END SUBROUTINE |
@@ -0,0 +1,337 @@ | |||||
SUBROUTINE PressureAnnAndOHDistribution | |||||
!! Record of revisions | |||||
!! Date Programmer Discription of change | |||||
!! ------ ------------ ----------------------- | |||||
!! 1396/07/30 Sheikh Original code | |||||
!! | |||||
USE FricPressDropVarsModule | |||||
USE MudSystemVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
USE GeoElements_FluidModule | |||||
USE Fluid_Flow_Startup_Vars | |||||
use KickVARIABLESModule | |||||
USE CMudPropertiesVariables | |||||
USE TD_WellGeometry | |||||
USE CReservoirVariables | |||||
use MudSystemModule | |||||
USE CHOKEVARIABLES | |||||
USE CChokeManifoldVariables | |||||
USE VARIABLES | |||||
USE CError | |||||
USE , INTRINSIC :: IEEE_ARITHMETIC | |||||
IMPLICIT NONE | |||||
INTEGER :: i , j , k , l | |||||
INTEGER :: ifric | |||||
REAL :: Fraction | |||||
KBOP = 0.0 | |||||
IF (WellHeadOpen .OR. NoGasPocket == 0) THEN !! (mud circulation is normal wellhead may be open or closed) OR (kick is in the well and well head is open) | |||||
!!!!! Determining flow rate in each section | |||||
i = AnnulusFirstEl | |||||
j = OpenholeFirstEl - 1 | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! flowrates due to external sources like pump and tripping | |||||
!WRITE (*,*) 'MudSystem%StringFlowRate', MudSystem%StringFlowRate | |||||
FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate = (ClingingFactor * FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%Area + FlowEl(StringFirstEl)%Area) * DrillStringSpeed * ConvMintoSec * Convft3toUSgal ! flowrate in annulus due to tripping | |||||
FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate = FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate + REAL(MudSystem%MudVolume_InjectedToBH) * ConvMintoSec / dt ! flowrate in annulus due to pump | |||||
!WRITE (*,*) 'Drillstring speed (ft/s)' , FlowEl(j)%FlowRate | |||||
!IF (NoWellToChokeEl > 0) THEN ! flowrate in choke line | |||||
! FlowEl(NoHorizontalEl + NoStringEl + NoAnnulusEl + 1 : NoHorizontalEl + NoStringEl + NoAnnulusEl + NoWellToChokeEl)%FlowRate = MudSystem%AnnulusFlowRate + (DeltaVolumePipe * ConvMinToSec / dt) | |||||
!END IF | |||||
IF (MudSystem%ShoeFractured) THEN ! reduction of flowrate due to formation fracture and lost circulation | |||||
!WRITE (*,*) ' SHoe fractured', PressureGauges(5), FlowEl(ShoeFlowElNo)%FlowRate | |||||
IF (ShoeFlowElNo > AnnulusLastEl) THEN ! shoe is in openhole | |||||
FlowEl(ShoeFlowElNo : NumbEl)%FlowRate = - MudSystem%Qlost | |||||
FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate = FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate - MudSystem%Qlost | |||||
ELSE ! shoe is in annulus | |||||
FlowEl(ShoeFlowElNo : OpenholeFirstEl - 1)%FlowRate = FlowEl(ShoeFlowElNo : OpenholeFirstEl - 1)%FlowRate - MudSystem%Qlost | |||||
END IF | |||||
END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! initial guess flowrates for opening BOP or choke line | |||||
IF (WellHeadWasOpen == .FALSE. .AND. NoGasPocket > 0 .AND. KickIteration == 1) THEN | |||||
IF (ChokeKroneckerDelta == 1) THEN ! flow on choke line | |||||
IF (TotalOpenChokeArea < 0.01 * Choke%ChokeAreaFullyOpen) THEN | |||||
WRITE (*,*) 'density , TotalOpenChokeArea' , DownHole%Density, TotalOpenChokeArea | |||||
TotalOpenChokeArea = 0.01 * Choke%ChokeAreaFullyOpen | |||||
END IF | |||||
Kchoke = (ChokeDensity / ((2.0 * 89158.0) * (0.26 * 0.61 * TotalOpenChokeArea)**2)) * 4.0 ! *4.d0: seyyed gofte | |||||
GasPocketFlowInduced%Array(:) = MIN((0.6 / NoGasPocket * SQRT(PressureGauges(2) / Kchoke)) , (0.05 * GasPocketNewVol%Array(:) * ConvFt3toUSgal / 60 / dt)) | |||||
WRITE (*,*) ' PressureGauges(2) , Kchoke' , PressureGauges(2) , Kchoke | |||||
WRITE (*,*) 'Initial guess after opening choke =', GasPocketFlowInduced%Array(1) | |||||
WRITE (*,*) ' valve 49 ', Manifold%Valve(49)%Status | |||||
WRITE (*,*) ' valve 47 ', Manifold%Valve(47)%Status | |||||
WRITE (*,*) ' valve 26 ', Manifold%Valve(26)%Status | |||||
WRITE (*,*) ' valve 30 ', Manifold%Valve(30)%Status | |||||
WRITE (*,*) ' valve 34 ', Manifold%Valve(34)%Status | |||||
WRITE (*,*) ' valve 63 ', Manifold%Valve(63)%Status | |||||
WRITE (*,*) ' valve 28 ', Manifold%Valve(28)%Status | |||||
WRITE (*,*) ' valve 33 ', Manifold%Valve(33)%Status | |||||
WRITE (*,*) ' valve 62 ', Manifold%Valve(62)%Status | |||||
WRITE (*,*) ' valve 36 ', Manifold%Valve(36)%Status | |||||
WRITE (*,*) ' valve 38 ', Manifold%Valve(38)%Status | |||||
ELSE ! flow through bell nipple | |||||
k = NoHorizontalEl + NoStringEl + NoAnnulusEl | |||||
KBOP = FlowEl(AnnulusLastEl)%Density / ((2.0 * 89158.0) * (0.26 * 0.61 * ShearRam%MinimumOpenArea_InBOP)**2) | |||||
GasPocketFlowInduced%Array(:) = MIN((0.1 / NoGasPocket * SQRT(PressureGauges(6) / KBOP)) , (0.05 * GasPocketNewVol%Array(:) * ConvFt3toUSgal / 60 / dt)) | |||||
WRITE (*,*) 'PressureGauges(6), KBOP', PressureGauges(6), KBOP | |||||
WRITE (*,*) 'Initial guess after opening BOP =', GasPocketFlowInduced%Array(1) | |||||
END IF | |||||
END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! flowrates due to expansion of gas pockets or kick influx | |||||
!i = AnnulusFirstEl | |||||
!j = OpenholeFirstEl - 1 | |||||
IF (NoGasPocket > 0) THEN | |||||
DO l = 1 , NoGasPocket !GasPocketFlowEl | |||||
k = GasPocketFlowEl(l , 1) | |||||
!WRITE (*,*) 'GasPocketFlowEl(l , 1)', l, k, j | |||||
IF (k == 0) CALL ERRORSTOP('GasPocketFlowEl(l , 1) == 0', l) | |||||
IF (k >= OpenholeFirstEl) THEN ! gas pocket is in open hole only | |||||
FlowEl(k : NumbEl)%FlowRate = FlowEl(k : NumbEl)%FlowRate + GasPocketFlowInduced%Array(l) ! openhole elements above pocket | |||||
FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate = FlowEl(AnnulusFirstEl : OpenholeFirstEl - 1)%FlowRate + GasPocketFlowInduced%Array(l) ! annulus and choke line elements | |||||
ELSE IF (k < OpenholeFirstEl) THEN ! gas pocket is in annulus ond/or choke line only | |||||
FlowEl(k : OpenholeFirstEl - 1)%FlowRate = FlowEl(k : OpenholeFirstEl - 1)%FlowRate + GasPocketFlowInduced%Array(l) ! annulus or choke line elements above pocket | |||||
END IF | |||||
END DO | |||||
END IF | |||||
!IF (ChokeKroneckerDelta == 1 .AND. ABS(FlowEl(i + NoAnnulusEl)%FlowRate / 600.0 - Ann_Saved_MudDischarged_Volume_Final) > 0.05) THEN | |||||
! WRITE (*,*) 'Difference between flowrates', FlowEl(i + NoAnnulusEl + 1)%FlowRate / 600.0, Ann_Saved_MudDischarged_Volume_Final | |||||
!END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!! END - Determining flow rate in each section | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! effect of surge and swab on frictional pressure drop direction | |||||
DO l = AnnulusFirstEl , OpenholeFirstEl - 1 | |||||
IF (FlowEl(l)%FlowRate < 0.0) THEN | |||||
FlowEl(l)%FrictionDirection = -1 | |||||
IF (FlowEl(l)%FlowRate > -1.0 * PressFlowrateTolerance .AND. ALLOCATED(GasPocketWeight%Array)) FlowEl(l)%FlowRate = - PressFlowrateTolerance | |||||
ELSE | |||||
FlowEl(l)%FrictionDirection = 1 | |||||
IF (FlowEl(l)%FlowRate < PressFlowrateTolerance .AND. ALLOCATED(GasPocketWeight%Array)) FlowEl(l)%FlowRate = PressFlowrateTolerance | |||||
END IF | |||||
END DO | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! Calculating Back Pressure, in well to pit path back pressure = 0 | |||||
! in well to choke manifold path back pressure is equal to pressure before choke not casing pressure | |||||
IF (ChokeKroneckerDelta == 1) THEN | |||||
IF (FlowEl(OpenholeFirstEl - 1)%FlowRate < 0.0) THEN | |||||
WRITE (*,*) ' Negative choke flowrate' | |||||
FlowEl(OpenholeFirstEl - 1)%FlowRate = MAX((REAL(MudSystem%MudVolume_InjectedToBH) * ConvMintoSec / dt) , 10.0) | |||||
END IF | |||||
!Kchoke = ChokeDensity / ((2. * 89158.0) * (0.26 * 0.61 * TotalOpenChokeArea)**2) | |||||
MudSystem%deltaPchoke = (Kchoke * FlowEl(OpenholeFirstEl - 1)%FlowRate * ABS(FlowEl(OpenholeFirstEl - 1)%FlowRate)) * 1.d0 | |||||
!WRITE (*,*) '**deltaPchoke , Kchoke, choke flowrate' , deltaPchoke , Kchoke, FlowEl(i)%FlowRate | |||||
!WRITE (*,*) '**TotalOpenChokeArea , Total Open Choke Area Percent' , TotalOpenChokeArea , TotalOpenChokeArea / 4.0 * ChokeAreaFullyOpen | |||||
IF (MudSystem%deltaPchoke < 0.d0) MudSystem%deltaPchoke = 0.d0 | |||||
BackPressure = REAL(MudSystem%deltaPchoke) | |||||
!WRITE (*,*) ' Choke inlet FlowRate, Density, pressure' , FlowEl(j)%FlowRate, FlowEl(j)%Density, FlowEl(j)%StartPress | |||||
!WRITE (*,*) ' Choke outlet Density' , FlowEl(i)%Density | |||||
!WRITE (*,*) ' deltaPchoke , choke flowrate' , deltaPchoke , FlowEl(i)%FlowRate | |||||
!WRITE (*,*) 'Total Open Choke Area Percent' , TotalOpenChokeArea / 4.0 * ChokeAreaFullyOpen | |||||
ELSE | |||||
BackPressure = 0.0 | |||||
END IF | |||||
IF (IEEE_IS_NaN(BackPressure)) CALL ErrorStop('NaN in calculating back pressure' , FlowEl(j)%FlowRate) | |||||
!write(*,*) 'BackPressure=' , BackPressure | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! when flow passes through choke manifold, solution process may be unstable | |||||
IF (ChokeKroneckerDelta == 1) THEN ! thus we should stabilize solution | |||||
IF (TotalOpenChokeArea > 0.5 * Choke%ChokeAreaFullyOpen) THEN | |||||
KickCorrectionUnderRelaxation = 0.6 | |||||
ELSE IF (TotalOpenChokeArea > 0.1 * Choke%ChokeAreaFullyOpen) THEN | |||||
KickCorrectionUnderRelaxation = 0.5 | |||||
ELSE ! TotalOpenChokeArea < 0.1 * ChokeAreaFullyOpen | |||||
KickCorrectionUnderRelaxation = 0.4 | |||||
END IF | |||||
ELSE | |||||
KickCorrectionUnderRelaxation = 0.6 | |||||
END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! calculating frictional pressure drop in annulus, chooke line and open hole elements | |||||
DO ifric = AnnulusFirstEl , NumbEl | |||||
CALL FricPressDrop(ifric) | |||||
!WRITE (*,*) ' element No, FlowRate , Density, FricPressLoss', ifric, FlowEl(ifric)%FlowRate, FlowEl(ifric)%Density, FlowEl(ifric)%FricPressLoss | |||||
IF (IEEE_IS_NaN(FlowEl(ifric)%FricPressLoss)) THEN | |||||
WRITE (*,*) 'H, S, A, Ch, O', NoHorizontalEl , NoStringEl , NoAnnulusEl , NoWellToChokeEl , NoOpenHoleEl | |||||
WRITE (*,*) 'Ann/Op start, end, density, Q, mu, Type' , FlowEl(ifric)%StartX, FlowEl(ifric)%EndX, FlowEl(ifric)%Density, FlowEl(ifric)%FlowRate, FlowEl(ifric)%mueff, FlowEl(ifric)%MaterialType | |||||
CALL ErrorStop('NaN in calculating pressure drop' , ifric) | |||||
END IF | |||||
END DO | |||||
!IF (ChokeKroneckerDelta == 1) THEN | |||||
!WRITE (*,*) ' velocity and flowrate', FlowEl(i)%vel, FlowEl(i)%flowrate | |||||
!WRITE (*,*) ' Theta600, Theta300', FlowEl(i)%Theta600 , FlowEl(i)%Theta300 | |||||
!WRITE (*,*) ' kIndex , nIndex', FlowEl(i)%kIndex, FlowEl(i)%nIndex | |||||
!WRITE (*,*) ' last el. mueff, gen. Rey.', i, FlowEl(i)%mueff, FlowEl(i)%GenRe | |||||
!END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! Pressure distribution in annulus | |||||
j = OpenholeFirstEl - 1 | |||||
FlowEl(OpenholeFirstEl - 1)%EndPress = BackPressure | |||||
FlowEl(OpenholeFirstEl - 1)%StartPress = FlowEl(OpenholeFirstEl - 1)%EndPress + FlowEl(OpenholeFirstEl - 1)%FricPressLoss + FlowEl(OpenholeFirstEl - 1)%StaticPressDiff | |||||
!write(*,*) 'FlowEl(j)%StartPress=' ,j, FlowEl(j)%StartPress | |||||
!write(*,*) 'FlowEl(j)%Length=' ,j, FlowEl(j)%Length, FlowEl(j)%EndX | |||||
!write(*,*) 'FlowEl(i)%dPdLFric=' ,i, FlowEl(i)%dPdLFric | |||||
DO l = OpenholeFirstEl - 2 , AnnulusFirstEl , -1 | |||||
!WRITE (*,*) '123' | |||||
FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress | |||||
FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%FricPressLoss + FlowEl(l)%StaticPressDiff | |||||
!WRITE(*,*) "ANNULUS: bottom , top Pressure", l , FlowEl(l)%StartPress , FlowEl(l)%EndPress , FlowEl(l)%fricPressLoss | |||||
!WRITE(*,*) "ANNULUS: Start , End X", FlowEl(l)%StartX , FlowEl(l)%EndX | |||||
!write(*,*) 'FlowEl(i)%StartPress=' ,i, FlowEl(i)%StartPress | |||||
!WRITE (*,*) ' FlowEl(i)%GenRe, FlowEl(i)%ReCritLam ' , FlowEl(i)%GenRe , FlowEl(i)%ReCritLam | |||||
END DO | |||||
!!!!!!!!!!!!!!!!! Pressure distribution in Open Hole | |||||
FlowEl(NumbEl)%EndPress = FlowEl(AnnulusFirstEl)%StartPress | |||||
FlowEl(NumbEl)%StartPress = FlowEl(NumbEl)%EndPress + FlowEl(NumbEl)%FricPressLoss + FlowEl(NumbEl)%StaticPressDiff | |||||
!WRITE (*,*) 'op top and op down' , FlowEl(NumbEl)%EndPress, FlowEl(j + 1)%StartPress | |||||
!write(*,*) 'FlowEl(NumbEl)%dPdLFric=' , FlowEl(NumbEl)%dPdLFric | |||||
!write(*,*) 'FlowEl(NumbEl)%dPdLGrav=' , FlowEl(NumbEl)%dPdLGrav | |||||
DO l = NumbEl - 1 , OpenholeFirstEl , -1 | |||||
!WRITE(*,*) ' ope' | |||||
FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress | |||||
!IF (FlowEl(i)%FlowRate < 0.0d0) THEN | |||||
! FlowEl(i)%StartPress = FlowEl(i)%EndPress - FlowEl(i)%FricPressLoss + FlowEl(i)%StaticPressDiff | |||||
!ELSE | |||||
FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%FricPressLoss + FlowEl(l)%StaticPressDiff | |||||
!WRITE (*,*) ' Length, static, frictional open' , FlowEl(i)%Length, FlowEl(i)%StaticPressDiff, FlowEl(i)%FricPressLoss | |||||
!END IF | |||||
END DO | |||||
ELSE ! wellhead is closed and kick is in the well | |||||
!WRITE (*,*) ' well head is closed' | |||||
k = GasPocketFlowEl(NoGasPocket , 1) | |||||
!WRITE (*,*) 'k, Pocket Press', k, GasPocketOldPress%Array(NoGasPocket) - StandardPress | |||||
i = AnnulusFirstEl | |||||
j = OpenholeFirstEl - 1 | |||||
FlowEl(k)%StartPress = GasPocketOldPress%Array(NoGasPocket) - StandardPress | |||||
FlowEl(k)%EndPress = GasPocketOldPress%Array(NoGasPocket) - StandardPress | |||||
IF (k > OpenholeFirstEl - 1) THEN ! Top pocket StartX is in Open hole | |||||
!WRITE (*,*) 'here 1' | |||||
DO l = k - 1 , OpenholeFirstEl , -1 ! below elements in openhole | |||||
!WRITE (*,*) 'here 1-1' | |||||
FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress | |||||
FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
DO l = k + 1 , NumbEl ! Above elements in openhole | |||||
!WRITE (*,*) 'here 1-2' | |||||
FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress | |||||
FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
FlowEl(AnnulusFirstEl)%StartPress = FlowEl(NumbEl)%EndPress | |||||
FlowEl(AnnulusFirstEl)%EndPress = FlowEl(AnnulusFirstEl)%StartPress - FlowEl(AnnulusFirstEl)%StaticPressDiff | |||||
DO l = AnnulusFirstEl + 1 , OpenholeFirstEl - 1 | |||||
FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress | |||||
FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
ELSE ! Top pocket StartX is in annulus or choke line | |||||
DO l = k - 1 , AnnulusFirstEl , -1 ! below elements in annnulus | |||||
FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress | |||||
FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
DO l = k + 1 , OpenholeFirstEl - 1 ! Above elements in annulus | |||||
FlowEl(l)%StartPress = FlowEl(l - 1)%EndPress | |||||
FlowEl(l)%EndPress = FlowEl(l)%StartPress - FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
FlowEl(NumbEl)%EndPress = FlowEl(AnnulusFirstEl)%StartPress | |||||
FlowEl(NumbEl)%StartPress = FlowEl(NumbEl)%EndPress + FlowEl(NumbEl)%StaticPressDiff | |||||
DO l = NumbEl - 1 , OpenholeFirstEl , -1 | |||||
FlowEl(l)%EndPress = FlowEl(l + 1)%StartPress | |||||
FlowEl(l)%StartPress = FlowEl(l)%EndPress + FlowEl(l)%StaticPressDiff | |||||
END DO | |||||
END IF | |||||
! | |||||
! !WRITE (*,*) ' first annulus bottom pressure ' , FlowEl(NoHorizontalEl + NoStringEl + 1)%StartPress | |||||
! !WRITE (*,*) ' last OpenHole bottom pressure' , FlowEl(NumbEl)%StartPress | |||||
! !WRITE (*,*) ' Gas Pocket pressure' , GasPocket%NewPress | |||||
END IF | |||||
!!!!!!!!!!!!!!!!!!!!!! checking pressure for preventing NaN in pressures | |||||
DO l = OpenholeFirstEl - 1 , AnnulusFirstEl , -1 ! annulus or choke elements | |||||
!WRITE (*,*) 'start, end' , FlowEl(i)%StartX, FlowEl(i)%EndX | |||||
IF (IEEE_IS_NaN(FlowEl(l)%EndPress)) THEN | |||||
WRITE (*,*) 'H, S, A, Ch, O', NoHorizontalEl , NoStringEl , NoAnnulusEl , NoWellToChokeEl , NoOpenHoleEl | |||||
WRITE (*,*) 'Ann/Ch start, end, density, Q, mu' , FlowEl(l)%StartX, FlowEl(l)%EndX, FlowEl(l)%Density, FlowEl(l)%FlowRate, FlowEl(l)%mueff, FlowEl(l)%MaterialType | |||||
CALL ERRORSTOP('NaN in EndPress', l) | |||||
END IF | |||||
END DO | |||||
DO l = NumbEl , OpenholeFirstEl - 1 , -1 ! op elements | |||||
!WRITE (*,*) 'start, end' , FlowEl(i)%StartX, FlowEl(i)%EndX | |||||
IF (IEEE_IS_NaN(FlowEl(l)%EndPress)) THEN | |||||
WRITE (*,*) 'H, S, A, Ch, O', NoHorizontalEl , NoStringEl , NoAnnulusEl , NoWellToChokeEl , NoOpenHoleEl | |||||
WRITE (*,*) 'Op start, end, density, Q, mu' , FlowEl(l)%StartX, FlowEl(l)%EndX, FlowEl(l)%Density, FlowEl(l)%FlowRate, FlowEl(l)%mueff, FlowEl(l)%MaterialType | |||||
CALL ERRORSTOP('NaN in EndPress', l) | |||||
END IF | |||||
END DO | |||||
!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!! | |||||
BottomHolePress = FlowEl(OpenholeFirstEl)%StartPress | |||||
!DO i = 1 , NoGasPocket | |||||
! WRITE (*,*) ' Pocket, Pressure, Vol, Flow Induced, FlowElPress', i, REAL(GasPocketNewPress%Array(i)), REAL(GasPocketNewVol%Array(i)), GasPocketFlowInduced%Array(i), FlowEl(GasPocketFlowEl(i , 1))%StartPress | |||||
!END DO | |||||
!WRITE (*,*) ' BottomHolePress =' , BottomHolePress | |||||
!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!IF (ChokeKroneckerDelta == 1) THEN | |||||
! WRITE (*,*) ' ChokeLine flowrate' , FlowEl(NoHorizontalEl + NoStringEl + NoAnnulusEl + NoWellToChokeEl)%FlowRate , MudSystem%StringFlowRate | |||||
! !i = NoHorizontalEl + NoStringEl + NoAnnulusEl | |||||
! !j = NoHorizontalEl + NoStringEl + NoAnnulusEl + NoWellToChokeEl | |||||
! !WRITE (*,*) ' Well Outlet and Chokeline Outlet Pressure' , FlowEl(i)%EndPress, FlowEl(j)%EndPress | |||||
!END IF | |||||
!IF (GasPocket%ElementNo == 0) THEN | |||||
! KickUnknownVector(2) = BottomHolePress | |||||
!!ELSE | |||||
!! KickUnknownVector(2) = FlowEl(GasPocket%ElementNo)%StartPress | |||||
!END IF | |||||
!IF (WellHeadOpen) | |||||
! GasPocket%NewPress = KickUnknownVector(2) | |||||
!END IF | |||||
!WRITE (*,*) 'Ann End' | |||||
END SUBROUTINE |
@@ -0,0 +1,118 @@ | |||||
SUBROUTINE FlowStartup | |||||
Use ConfigurationVariables | |||||
USE Fluid_Flow_Startup_Vars | |||||
USE CStringConfigurationVariables | |||||
USE CMudPropertiesVariables | |||||
USE FricPressDropVarsModule | |||||
use KickVARIABLESModule | |||||
USE MudSystemVARIABLES | |||||
use PressureDisplayVARIABLESModule | |||||
USE CShoeVariables | |||||
USE TD_DrillStemComponents | |||||
USE TD_WellGeometry, pi3 => pi | |||||
USE CPathGenerationVariables | |||||
USE CWellSurveyDataVariables | |||||
Use CHOKEVARIABLES, pi4 => pi | |||||
IMPLICIT NONE | |||||
INTEGER :: i | |||||
PressureGauges(:) = 0.0 | |||||
KickSinglePocket = Reservoir%MakeKickSinglePacket | |||||
IF (KickSinglePocket) THEN | |||||
MaxGasPocket = 1 | |||||
ELSE | |||||
MaxGasPocket = 4 | |||||
END IF | |||||
MaxChokeDensityChange = 25.0 ! [ppg/min] | |||||
ChokeMinDensity = 2.0 | |||||
ChokeDensity = MudProperties%ActiveDensity | |||||
MinKickVol = 0.5 ! USGal | |||||
SecondaryKickVol = 0.0 | |||||
SecondaryKickWeight = 0.0 | |||||
NoGasPocket = 0 ! No Kick | |||||
WellHeadOpen = .TRUE. | |||||
WellHeadWasOpen = .TRUE. | |||||
BackPressure = 0.0 | |||||
GasKickPumpFlowRate = 0.0 | |||||
DownHole%KickVolume = 0.0 | |||||
DownHole%InfluxRate = 0.0 | |||||
ExitMass = 0.0 | |||||
MinAllowableKickVol = 1.0 * (42.0 / Convft3toUSgal) ! 1 bbl * 42 gal/bbl / 7.48 gal/ft^3 = ... ft^3 | |||||
StCompressedMudVol = 0.0 | |||||
AnnCompressedMudVol = 0.0 | |||||
KickFlux = .FALSE. | |||||
KickOffBottom = .FALSE. | |||||
KickWasExitingThroughChoke = .FALSE. | |||||
FloatValveOpen = .TRUE. | |||||
Choke%ChokeAreaFullyOpen = 123.0 / 64.0 ! fully open area is 123/64 in^2 = 0.01334635 ft^2 | |||||
ChokeBypassArea = PI / 4.0 * BopStackSpecification%ChokeLineId**2 | |||||
BHPSafetyMargin = 150.0 | |||||
AChBHPTol = 15.0 | |||||
ManChoke1Plug = 0 | |||||
ManChoke2Plug = 0 | |||||
ManChoke1Washout = 0 | |||||
ManChoke2Washout = 0 | |||||
BitJetsPlugged = 0 | |||||
BitJetsWashedOut = 0 | |||||
CasingPressure_DataDisplayMalF = 0 | |||||
SoundSpeed = 1530.0 / Convfttom | |||||
PressureTimeStepDelay(1) = INT(2.0 * SUM(Configuration%StringConfiguration%StringConfigurations(2:)%ComponentLength) / SoundSpeed / dt) | |||||
PressureTimeStepDelay(2) = INT(PathGeneration%Items(SIZE(PathGeneration%Items))%MeasuredDepth / SoundSpeed / dt) | |||||
PressureTimeStepDelay(3) = INT(Shoe%ShoeDepth / SoundSpeed / dt) | |||||
!WRITE (*,*) SUM(StringConfigurations(2:)%ComponentLength), PathGenerations(SIZE(PathGenerations))%TotalVerticalDepth!, WellSurveyData(SIZE(WellSurveyData))%TotalVerticalDepth | |||||
!WRITE (*,*) PathGenerations(SIZE(PathGenerations))%MeasuredDepth!, WellSurveyData(SIZE(WellSurveyData))%MeasuredDepth | |||||
WRITE (*,*) 'time step delay', PressureTimeStepDelay | |||||
DO i = 1 , PressureTimeStepDelay(1) | |||||
CALL PumpPressureDelay%AddToFirst(0.0) | |||||
END DO | |||||
DO i = 1 , PressureTimeStepDelay(2) | |||||
CALL BottomHolePressureDelay%AddToFirst(REAL(0.052 * MudProperties%ActiveDensity * PathGeneration%Items(SIZE(PathGeneration%Items))%TotalVerticalDepth)) | |||||
END DO | |||||
DO i = 1 , PressureTimeStepDelay(3) | |||||
CALL ShoePressureDelay%AddToFirst(REAL(0.052 * MudProperties%ActiveDensity * Shoe%ShoeDepth)) | |||||
END DO | |||||
!!!!!!! Methane Information | |||||
GasType(1)%CritPress = 673.0 | |||||
GasType(1)%CritTemp = 344.0 | |||||
GasType(1)%MolarWt = 16.04 | |||||
GasType(1)%StDensity = 0.04238 | |||||
GasType(1)%GasConstant = RUniversal / GasType(1)%MolarWt | |||||
!!!!!!!! H2S Information | |||||
GasType(2)%CritPress = 1306.0 | |||||
GasType(2)%CritTemp = 673.0 | |||||
GasType(2)%MolarWt = 34.08 | |||||
GasType(2)%StDensity = 0.09087 | |||||
GasType(2)%GasConstant = RUniversal / GasType(2)%MolarWt | |||||
!!!!!!!! CO2 Information | |||||
GasType(3)%CritPress = 1072.0 | |||||
GasType(3)%CritTemp = 548.0 | |||||
GasType(3)%MolarWt = 44.01 | |||||
!GasType(3)%StDensity = 00 | |||||
GasType(3)%GasConstant = RUniversal / GasType(2)%MolarWt | |||||
!!!!!!!! Mud density and viscosity | |||||
Theta600Refrence = MudProperties%ActiveThetaSixHundred | |||||
Theta300Refrence = MudProperties%ActiveThetaThreeHundred | |||||
DensityRefrence = MudProperties%ActiveDensity | |||||
END SUBROUTINE |
@@ -0,0 +1,64 @@ | |||||
MODULE Fluid_Flow_Startup_Vars | |||||
!!! In this module constants and conversion factors are stated | |||||
REAL , PARAMETER :: RUniversal = 10.73159 ! [psia.ft^3/(lbmole.R)] | |||||
REAL , PARAMETER :: RUniversalSI = 8.314 * 10**6 ! [Pa.cm^3/(mole.K)] | |||||
REAL , PARAMETER :: PI = 3.141593 ! Pi number | |||||
REAL , PARAMETER :: StandardPress = 14.7 ! [psia] | |||||
REAL , PARAMETER :: StandardTemp = 519.67 ! 60 F [R] , Temp F = Temp R + 459.67 | |||||
REAL , PARAMETER :: dt = 0.1 ! time step = 0.1 [s] | |||||
REAL , PARAMETER :: GasDensityRefrence = 28.96 ! molar weight of air [lbm/lbmole] | |||||
!! Tolerance and convergence or error criteria | |||||
REAL , PARAMETER :: UTubePressTolerance = 4 ! minimum pressure tolerance between two arms of U tube for which calculations will stop [psi] | |||||
!REAL , PARAMETER :: PressDensityTolerance = 2 ! Pressure Density Tolerance: for flow elements with density below this amount (usually gas pockets), | |||||
! frictional and gravitional pressure gradients are neglected [ppg] | |||||
REAL , PARAMETER :: PressLengthTolerance = 0.0 ! Pressure Length Tolerance: for flow elements with length below this amount, | |||||
! frictional and gravitional pressure gradients are neglected [ft] | |||||
REAL , PARAMETER :: PressFlowrateTolerance = 0.2 ! Pressure Flowrate Tolerance: for flow elements with flowrates below this amount, | |||||
! frictional pressure gradients are neglected [gpm] | |||||
REAL , PARAMETER :: KickConvergenceTolerance = 0.05 ! absolute value of maximum error in calculation of gas kick pressure and flowrate | |||||
!!!!!!!!!!!!!!!!!! Conversion factors | |||||
REAL , PARAMETER :: Convlbftolbm = 32.174 ! 1 lbf = 32.174 lbm*ft/s^2 | |||||
REAL , PARAMETER :: Convft3toUSgal = 7.48052 ! 1 ft^3 = 7.48052 US gal | |||||
REAL , PARAMETER :: Convfttom = 0.3048 ! 1 ft = 0.3048 m | |||||
REAL , PARAMETER :: Convfttoinch = 12.0 ! 1 ft = 12 inch | |||||
REAL , PARAMETER :: Convdaytohour = 24.0 ! 1 day = 24 hour | |||||
REAL , PARAMETER :: Convhourtomin = 60.0 ! 1 hour = 60 min | |||||
REAL , PARAMETER :: Convmintosec = 60.0 ! 1 min = 60 sec | |||||
REAL , PARAMETER :: ConvpsitoPa = 6894.76 ! 1 psi = 6894.76 pa | |||||
REAL , PARAMETER :: ConvRtoK = 0.555556 ! 1 R = 0.555556 K | |||||
REAL , PARAMETER :: Convpcftogpcm3 = 0.0160185 ! 1 lbm/ft^3 = 0.0160185 gr/cm^3 | |||||
!!!!!!!!!!!!!!!!! | |||||
!!!!!!! Bit data !!!!!! | |||||
! Type :: BitDataType | |||||
LOGICAL :: BitTrue ! bit may be present (.TRUE.) or may be absent(.FALSE.) | |||||
REAL :: BitNozzleArea ! area of a nozzle | |||||
INTEGER :: BitNozzleNum ! Number of bit nozzles | |||||
REAL :: BitNozzDia ! nozzle diameter in 1/32 in | |||||
REAL :: BitTotNozzArea ! Total bit area | |||||
REAL :: BitCd ! Discharge coefficient | |||||
REAL :: BitPressLoss ! bit pressure loss [psi] | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
REAL :: Theta600Refrence , Theta300Refrence ! Fann data (Theta600 and Theta300) of active tank (input from panel) | |||||
REAL :: DensityRefrence ! Density of active tank mud (input from panel) [gpm] | |||||
! End Type BitDataType | |||||
! Type(BitDataType)::BitData | |||||
TYPE, PUBLIC :: GasData | |||||
REAL :: CritPress ! critical pressure [psia] | |||||
REAL :: CritTemp ! critical temperature [R] | |||||
REAL :: MolarWt ! molar weight [lbm/lbmole] | |||||
REAL :: StDensity ! density at standard pressure (14.7 psi) and temperature (60 F = 520 Ra) [lbm/ft^3] | |||||
REAL :: GasConstant ! Gas constant = RUniversal/MolarWt [psia.ft^3/(R.lbm)] | |||||
END TYPE GasData | |||||
TYPE(GasData) :: GasType(3) ! 1 = methane , 2 = Hydrogen sulfide , 3 = Carbon dioxid | |||||
END MODULE | |||||
@@ -0,0 +1,147 @@ | |||||
module FluidFlowMain | |||||
implicit none | |||||
public | |||||
contains | |||||
! | |||||
! subroutine FluidFlow_Setup() | |||||
! ! use CSimulationVariables | |||||
! implicit none | |||||
! !call OnSimulationInitialization%Add(FluidFlow_Init) | |||||
! call OnSimulationStop%Add(FluidFlow_Stop) | |||||
! call OnFluidFlowStart%Add(FluidFlow_Start) | |||||
! call OnFluidFlowStep%Add(FluidFlow_Step) | |||||
! !call OnFluidFlowOutput%Add(FluidFlow_Output) | |||||
! call OnFluidFlowMain%Add(FluidFlowMainBody) | |||||
! end subroutine | |||||
! subroutine FluidFlow_Stop | |||||
! implicit none | |||||
! !WRITE (*,*) ' fluid flow done_Stop' | |||||
! call DEALLOCATE_ARRAYS_NormalCirculation() | |||||
! CALL DeallocateFlowTypes | |||||
! end subroutine FluidFlow_Stop | |||||
subroutine FluidFlow_Init | |||||
USE Fluid_Flow_Startup_Vars | |||||
implicit none | |||||
!WRITE (*,*) ' fluid flow done_Start' | |||||
CALL NormalCirculation_StartUp() | |||||
CALL FlowStartup | |||||
Call TD_StartUp | |||||
Call TD_WellReadData | |||||
Call TD_WellElementsReadData | |||||
Call TD_DrillStemReadData | |||||
Call TD_PipePropertiesReadData | |||||
end subroutine FluidFlow_Init | |||||
subroutine FluidFlow_Step | |||||
implicit none | |||||
integer :: i, FlowDuration, SimulationStateOld | |||||
integer,dimension(8) :: FlowStartTime,FlowEndTime | |||||
!WRITE (*,*) ' fluid flow done_Step' | |||||
!call Fluid_Flow_Solver | |||||
CALL DATE_AND_TIME(values=FlowStartTime) | |||||
call Fluid_Flow_Solver | |||||
CALL DATE_AND_TIME(values=FlowEndTime) | |||||
FlowDuration = 3600000 * (FlowEndTime(5) - FlowStartTime(5)) + 60000 * (FlowEndTime(6) - FlowStartTime(6)) + 1000 * (FlowEndTime(7) - FlowStartTime(7)) + (FlowEndTime(8) - FlowStartTime(8)) | |||||
WRITE (*,*) 'FlowDuration (ms)=' , FlowDuration | |||||
end subroutine FluidFlow_Step | |||||
!subroutine FluidFlow_Output | |||||
! implicit none | |||||
!end subroutine FluidFlow_Output | |||||
! subroutine FluidFlowMainBody | |||||
! ! | |||||
! use ifport | |||||
! use ifmt | |||||
! ! use CSimulationVariables | |||||
! USE Fluid_Flow_Startup_Vars | |||||
! !use general_info, only : reset_data | |||||
! !use well_info | |||||
! !use drilling_info | |||||
! use CLog1 | |||||
! ! | |||||
! implicit none | |||||
!integer :: i, FlowDuration, SimulationStateOld | |||||
!integer,dimension(8) :: FlowStartTime,FlowEndTime | |||||
! | |||||
! | |||||
!CALL NormalCirculation_StartUp() | |||||
!CALL FlowStartup | |||||
! | |||||
!Call TD_StartUp | |||||
!Call TD_WellReadData | |||||
!Call TD_WellElementsReadData | |||||
!Call TD_DrillStemReadData | |||||
!Call TD_PipePropertiesReadData | |||||
! | |||||
! | |||||
!LoopSimulation: do | |||||
! !WRITE (*,*) ' fluid flow done 0' | |||||
!! | |||||
! CALL DATE_AND_TIME(values=FlowStartTime) | |||||
! !WRITE (*,*) 'FlowStartTime=', FlowStartTime | |||||
!! | |||||
! call Fluid_Flow_Solver | |||||
! | |||||
!! | |||||
! CALL DATE_AND_TIME(values=FlowEndTime) | |||||
!! | |||||
! !WRITE (*,*) ' fluid flow done 1' | |||||
! | |||||
! | |||||
! | |||||
! FlowDuration = 3600000 * (FlowEndTime(5) - FlowStartTime(5)) + 60000 * (FlowEndTime(6) - FlowStartTime(6)) + 1000 * (FlowEndTime(7) - FlowStartTime(7)) + (FlowEndTime(8) - FlowStartTime(8)) | |||||
! | |||||
! | |||||
! !call Log_1('FlowDuration=', FlowDuration) | |||||
! !WRITE (*,*) 'FlowDuration (ms)=' , FlowDuration | |||||
! | |||||
! if ((100 - FlowDuration) > 0) then | |||||
! !WRITE (*,*) 'fluid flow done 2' | |||||
! call sleepqq(100 - FlowDuration) | |||||
! !WRITE (*,*) ' fluid flow done 3' | |||||
! | |||||
! end if | |||||
! !WRITE (*,*) ' fluid flow done 4' | |||||
! | |||||
! | |||||
! | |||||
! !WRITE (*,*) "FlowDuration", FlowDuration | |||||
! !if(IsStopped) then | |||||
! ! EXIT LoopSimulation | |||||
! !ENDIF | |||||
! !write(*,*) 'IsStopped=' , IsStopped | |||||
! | |||||
! if(IsStopped) then | |||||
! !write(*,*) '44444444444' | |||||
! | |||||
! call DEALLOCATE_ARRAYS_NormalCirculation() | |||||
! CALL DeallocateFlowTypes | |||||
! call Quit() | |||||
! end if | |||||
! ! | |||||
! ! if(IsStopped) exit LoopSimulation | |||||
! ! | |||||
!end do LoopSimulation | |||||
!!call DEALLOCATE_ARRAYS_NormalCirculation() | |||||
!!CALL DeallocateFlowTypes | |||||
! | |||||
! | |||||
! end subroutine FluidFlowMainBody | |||||
end module FluidFlowMain |
@@ -0,0 +1,58 @@ | |||||
subroutine Fluid_Flow_Solver | |||||
Use GeoElements_FluidModule | |||||
use UTUBEVARSModule | |||||
use KickVARIABLESModule | |||||
use PressureDisplayVARIABLESModule | |||||
USE FricPressDropVarsModule | |||||
USE MudSystemVARIABLES | |||||
USE Fluid_Flow_Startup_Vars | |||||
USE CError | |||||
implicit none | |||||
INTEGER :: FlowDuration | |||||
Integer :: qwer | |||||
integer,dimension(8) :: FlowStartTime,FlowEndTime | |||||
!WRITE (*,*) ' fluid flow pointer 1' | |||||
CALL TD_MainCalculations | |||||
Call MeshGeneration_FluidModule | |||||
!WRITE (*,*) ' fluid flow pointer 2' | |||||
MudSystem%FluidFlowCounter = MudSystem%FluidFlowCounter + 1 | |||||
call CirculationCodeSelect | |||||
CALL WellPressureDataTransfer | |||||
CALL FormationInformationCalculator | |||||
DO KickIteration = 1 , 40 | |||||
!WRITE (*,*) ' Kick Iteration', KickIteration | |||||
CALL PressureAnnAndOHDistribution | |||||
IF (NoGasPocket > 0) THEN | |||||
!KickCorrectionVector(:) = 1. | |||||
CALL GasKickCalculator | |||||
END IF | |||||
IF (NoGasPocket == 0 .OR. NOT(WellHeadOpen)) EXIT | |||||
IF(MAXVAL(ABS(KickVandPFunction(:))) < KickConvergenceTolerance) EXIT | |||||
!IF(MAXVAL(ABS(KickCorrectionVector(:))) < KickConvergenceTolerance) EXIT | |||||
END DO | |||||
CALL PressureHorizAndStringDistribution | |||||
IF (KickIteration == 41) THEN | |||||
WRITE (*,*) ' KickCorrectionVector ' , KickCorrectionVector | |||||
WRITE (*,*) ' Kick Jacobian = ', KickJacobian | |||||
END IF | |||||
end subroutine |
@@ -0,0 +1,230 @@ | |||||
SUBROUTINE FricPressDrop(iloc) | |||||
!! Record of revisions | |||||
!! Date Programmer Discription of change | |||||
!! ------ ------------ ----------------------- | |||||
!! 1396/07/23 Sheikh Original code | |||||
!! | |||||
USE FricPressDropVarsModule | |||||
USE CMudPropertiesVariables | |||||
USE Fluid_Flow_Startup_Vars | |||||
USE CError | |||||
IMPLICIT NONE | |||||
INTEGER :: iloc | |||||
REAL :: TauZero | |||||
TauZero = 12.0 | |||||
!ActiveRheologyModel = Herschel_Bulkley_RheologyModel | |||||
! 0 = Power Law , 1 = Bingham Plastic , 2 = Newtonian | |||||
!TotFricPressLoss = 0.0 | |||||
FlowEl(iloc)%alpha = 1 ! assume that all elements have annulus geometry | |||||
FlowEl(iloc)%dPdLfric = 0.0 | |||||
FlowEl(iloc)%f = 0.0 | |||||
FlowEl(iloc)%FlowRate = ABS(FlowEl(iloc)%FlowRate) | |||||
IF ((FlowEl(iloc)%FlowRate >= PressFlowrateTolerance) & | |||||
.AND. (FlowEl(iloc)%MaterialType /= 1) & ! not gas kick | |||||
.AND. (ABS(FlowEl(iloc)%Length) >= PressLengthTolerance) & | |||||
.AND. (FlowEl(iloc)%MaterialType /= 4)) THEN ! not air | |||||
IF (FlowEl(iloc)%Id==0) THEN | |||||
FlowEl(iloc)%alpha = 0 | |||||
END IF | |||||
FlowEl(iloc)%muPlastic = FlowEl(iloc)%Theta600 - FlowEl(iloc)%Theta300 ! cp | |||||
FlowEl(iloc)%YieldP = 2.0 * FlowEl(iloc)%Theta300 - FlowEl(iloc)%Theta600 ! lbf/100ft**2 | |||||
FlowEl(iloc)%nIndex = 3.32 * log10(FlowEl(iloc)%Theta600 / FlowEl(iloc)%Theta300) | |||||
FlowEl(iloc)%kIndex = 510.0 * FlowEl(iloc)%Theta300 / (511.0**FlowEl(iloc)%nIndex) ! rabete fv2 | |||||
IF (MudProperties%ActiveRheologyModel == Herschel_Bulkley_RheologyModel .AND. FlowEl(iloc)%alpha == 0) THEN | |||||
FlowEl(iloc)%kIndex = 1.066 * FlowEl(iloc)%Theta300 / (511.0**FlowEl(iloc)%nIndex) | |||||
ELSE IF (MudProperties%ActiveRheologyModel == Herschel_Bulkley_RheologyModel .AND. FlowEl(iloc)%alpha == 1) THEN | |||||
FlowEl(iloc)%nIndex = 3.32 * log10((FlowEl(iloc)%Theta600 - TauZero) / (FlowEl(iloc)%Theta300 - TauZero)) | |||||
FlowEl(iloc)%kIndex = 1.066 * (FlowEl(iloc)%Theta300 - TauZero) / (511.0**FlowEl(iloc)%nIndex) | |||||
END IF | |||||
! Calculating velocity | |||||
FlowEl(iloc)%vel = 0.408 * FlowEl(iloc)%FlowRate / (FlowEl(iloc)%Od**2 - FlowEl(iloc)%Id**2) ! velocity in ft/s | |||||
!FlowEl(iloc)%vel = 24.51 * FlowEl(iloc)%FlowRate / (FlowEl(iloc)%Od**2 - FlowEl(iloc)%Id**2) ! velocity in ft/min | |||||
!IF (FlowModel == Bingham_RheologyModel) THEN ! Bingham Plastic | |||||
! FlowEl(iloc)%Gf = (2. + FlowEl(iloc)%alpha) / 2. | |||||
!ELSE IF (FlowModel == PowerLow_RheologyModel) THEN | |||||
! FlowEl(iloc)%Gf = ((3. - FlowEl(iloc)%alpha) * FlowEl(iloc)%nIndex + 1.) / FlowEl(iloc)%nIndex / (4. - FlowEl(iloc)%alpha) * (2. + FlowEl(iloc)%alpha) / 2. | |||||
!END IF | |||||
!FlowEl(iloc)%gammaW = 1.6 * FlowEl(iloc)%Gf * FlowEl(iloc)%vel / FlowEl(iloc)%Dhyd | |||||
!IF (FlowModel == Bingham_RheologyModel) THEN ! Bingham Plastic | |||||
! FlowEl(iloc)%tauW = 1.067 * ((4. - FlowEl(iloc)%alpha) / (3. - FlowEl(iloc)%alpha) * FlowEl(iloc)%YieldP + FlowEl(iloc)%muPlastic * FlowEl(iloc)%gammaW) | |||||
! !FlowEl(iloc)%tauW = 1.067*(FlowEl(iloc)%YieldP+FlowEl(iloc)%muPlastic*FlowEl(iloc)%gammaW) | |||||
!ELSE IF (FlowModel == PowerLow_RheologyModel) THEN ! Power law | |||||
! FlowEl(iloc)%tauW = 1.067 * FlowEl(iloc)%kIndex * FlowEl(iloc)%gammaW**FlowEl(iloc)%nIndex | |||||
!END IF | |||||
! Calculating effective or apparent viscosity | |||||
IF (MudProperties%ActiveRheologyModel == Bingham_RheologyModel) THEN ! Bingham Plastic | |||||
FlowEl(iloc)%mueff = FlowEl(iloc)%muPlastic + 5. * FlowEl(iloc)%YieldP * FlowEl(iloc)%Dhyd / FlowEl(iloc)%vel | |||||
!write(*,*) 'pointer1' , FlowEl(iloc)%muPlastic , FlowEl(iloc)%YieldP , FlowEl(iloc)%Dhyd , FlowEl(iloc)%vel | |||||
ELSE IF (MudProperties%ActiveRheologyModel == PowerLaw_RheologyModel .OR. MudProperties%ActiveRheologyModel == Herschel_Bulkley_RheologyModel) THEN ! Power Law | |||||
FlowEl(iloc)%Gf = ((3. - FlowEl(iloc)%alpha) * FlowEl(iloc)%nIndex + 1.0) / FlowEl(iloc)%nIndex / (4.0 - FlowEl(iloc)%alpha) * (2.0 + FlowEl(iloc)%alpha) / 2.0 | |||||
FlowEl(iloc)%mueff = (FlowEl(iloc)%kIndex) / (1. + FlowEl(iloc)%alpha / 2.) * ((96. * FlowEl(iloc)%vel / FlowEl(iloc)%Dhyd)**(FlowEl(iloc)%nIndex - 1)) * FlowEl(iloc)%Gf**FlowEl(iloc)%nIndex | |||||
!write(*,*) 'pointer2' , FlowEl(iloc)%kIndex ,FlowEl(iloc)%alpha , FlowEl(iloc)%vel ,FlowEl(iloc)%Dhyd,FlowEl(iloc)%nIndex ,FlowEl(iloc)%Gf ,FlowEl(iloc)%nIndex | |||||
END IF | |||||
FlowEl(iloc)%gammaW = 96.0 * FlowEl(iloc)%Gf * FlowEl(iloc)%vel / FlowEl(iloc)%Dhyd | |||||
FlowEl(iloc)%tauW = ((4.0 - FlowEl(iloc)%alpha) / (3.0 - FlowEl(iloc)%alpha))**FlowEl(iloc)%nIndex * TauZero + FlowEl(iloc)%kIndex * FlowEl(iloc)%gammaW**FlowEl(iloc)%nIndex | |||||
! Calculating Reynolds number | |||||
IF (FlowEl(iloc)%Od == FlowEl(iloc)%Dhyd) THEN | |||||
FlowEl(iloc)%GenRe = 928. * FlowEl(iloc)%density * FlowEl(iloc)%vel * FlowEl(iloc)%Dhyd / FlowEl(iloc)%mueff | |||||
ELSE | |||||
FlowEl(iloc)%GenRe = 757. * FlowEl(iloc)%density * FlowEl(iloc)%vel * FlowEl(iloc)%Dhyd / FlowEl(iloc)%mueff | |||||
END IF | |||||
!FlowEl(iloc)%GenRe = 2997 * FlowEl(iloc)%density * FlowEl(iloc)%vel**2 / 19.36 / FlowEl(iloc)%tauW | |||||
! Calculating friction factor | |||||
IF (MudProperties%ActiveRheologyModel == Bingham_RheologyModel) THEN ! Bingham Plastic | |||||
IF (FlowEl(iloc)%GenRe <= 2000.0) THEN ! laminar regime | |||||
FlowEl(iloc)%f = 16.0 / FlowEl(iloc)%GenRe | |||||
ELSE IF (FlowEl(iloc)%GenRe >= 4000.0) THEN ! turbulent regime | |||||
FlowEl(iloc)%a = 0.0791 | |||||
FlowEl(iloc)%b = 0.25 | |||||
FlowEl(iloc)%f = FlowEl(iloc)%a / FlowEl(iloc)%GenRe**FlowEl(iloc)%b | |||||
ELSE !! transition from laminar to turbulent regime | |||||
FlowEl(iloc)%a = 0.0791 | |||||
FlowEl(iloc)%b = 0.25 | |||||
FlowEl(iloc)%f = (4000.0 - FlowEl(iloc)%GenRe) / 2000.0 * 16. / FlowEl(iloc)%GenRe & | |||||
+ (FlowEl(iloc)%GenRe - 2000.0) / 2000.0 * FlowEl(iloc)%a / FlowEl(iloc)%GenRe**FlowEl(iloc)%b | |||||
END IF | |||||
ELSE IF (MudProperties%ActiveRheologyModel == PowerLaw_RheologyModel) THEN ! Power law | |||||
FlowEl(iloc)%ReCritLam = 3470. - 1370. * FlowEl(iloc)%nIndex | |||||
FlowEl(iloc)%ReCritTurb = 4270. - 1370. * FlowEl(iloc)%nIndex | |||||
IF (FlowEl(iloc)%GenRe <= FlowEl(iloc)%ReCritLam) THEN ! laminar regime | |||||
FlowEl(iloc)%f = 16.0 / FlowEl(iloc)%GenRe / (1 - 0.184 * FlowEl(iloc)%alpha) | |||||
ELSE IF (FlowEl(iloc)%GenRe >= FlowEl(iloc)%ReCritTurb) THEN ! turbulent regime | |||||
FlowEl(iloc)%a = (log10(FlowEl(iloc)%nIndex) + 3.93) / 50. | |||||
FlowEl(iloc)%b = (1.75 - log10(FlowEl(iloc)%nIndex)) / 7. | |||||
FlowEl(iloc)%f = FlowEl(iloc)%a / FlowEl(iloc)%GenRe**FlowEl(iloc)%b | |||||
ELSE | |||||
FlowEl(iloc)%a = (log10(FlowEl(iloc)%nIndex) + 3.93) / 50. | |||||
FlowEl(iloc)%b = (1.75 - log10(FlowEl(iloc)%nIndex)) / 7. | |||||
FlowEl(iloc)%f = (FlowEl(iloc)%ReCritTurb - FlowEl(iloc)%GenRe) / 800.0 * 16. / FlowEl(iloc)%GenRe & | |||||
+ (FlowEl(iloc)%GenRe - FlowEl(iloc)%ReCritLam) / 800.0 * FlowEl(iloc)%a / FlowEl(iloc)%GenRe**FlowEl(iloc)%b | |||||
END IF | |||||
END IF | |||||
!WRITE (*,*) 'fric press drop', iloc | |||||
!WRITE (*,*) 'Length', ABS(REAL(FlowEl(iloc)%Length)) | |||||
!WRITE (*,*) 'FlowRate', FlowEl(iloc)%FlowRate | |||||
!WRITE (*,*) 'Theta600 , Theta300', FlowEl(iloc)%Theta600 , FlowEl(iloc)%Theta300 | |||||
!WRITE (*,*) 'Dhyd', FlowEl(iloc)%Dhyd | |||||
!WRITE (*,*) 'GenRe', FlowEl(iloc)%GenRe | |||||
!WRITE (*,*) 'f', FlowEl(iloc)%f | |||||
END IF | |||||
! Frictional pressure loss gradient calculation | |||||
! FlowEl(iloc)%dPdLfric = 1.076 * FlowEl(iloc)%f * FlowEl(iloc)%vel**2 * FlowEl(iloc)%density / 10**5 / FlowEl(iloc)%Dhyd | |||||
FlowEl(iloc)%dPdLfric = FlowEl(iloc)%f * (FlowEl(iloc)%vel)**2 * FlowEl(iloc)%density / 25.81 / FlowEl(iloc)%Dhyd | |||||
FlowEl(iloc)%FricPressLoss = FlowEl(iloc)%dPdLfric * ABS(REAL(FlowEl(iloc)%Length)) | |||||
IF (FlowEl(iloc)%FrictionDirection == -1) THEN | |||||
FlowEl(iloc)%FlowRate = - FlowEl(iloc)%FlowRate | |||||
FlowEl(iloc)%dPdLfric = - FlowEl(iloc)%dPdLfric | |||||
FlowEl(iloc)%FricPressLoss = - FlowEl(iloc)%FricPressLoss | |||||
END IF | |||||
!END DO | |||||
END SUBROUTINE FricPressDrop | |||||
SUBROUTINE PartialDerivativeFricToFlowRate(iloc) | |||||
USE FricPressDropVarsModule | |||||
USE CMudPropertiesVariables | |||||
USE Fluid_Flow_Startup_Vars | |||||
use KickVARIABLESModule | |||||
USE CError | |||||
IMPLICIT NONE | |||||
INTEGER :: iloc | |||||
FlowEl(iloc)%FricToQPartialDiff = 0.0 | |||||
!FlowEl(iloc)%FlowRate = ABS(FlowEl(iloc)%FlowRate) | |||||
IF ((ABS(FlowEl(iloc)%FlowRate) >= PressFlowrateTolerance) & | |||||
.AND. (FlowEl(iloc)%MaterialType /= 1) & ! not gas kick | |||||
.AND. (ABS(FlowEl(iloc)%Length) >= PressLengthTolerance) & | |||||
.AND. (FlowEl(iloc)%MaterialType /= 4)) THEN ! not air | |||||
IF (MudProperties%ActiveRheologyModel == PowerLaw_RheologyModel) THEN ! Power law | |||||
!IF (FlowEl(iloc)%Flowrate == 0.0) THEN | |||||
! FlowEl(iloc)%Flowrate = 10.0 | |||||
! CALL FricPressDrop(iloc) | |||||
!END IF | |||||
IF (FlowEl(iloc)%GenRe <= FlowEl(iloc)%ReCritLam) THEN ! laminar flow | |||||
FlowEl(iloc)%FricToQPartialDiff = FlowEl(iloc)%FricPressLoss / FlowEl(iloc)%FlowRate * FlowEl(iloc)%nIndex | |||||
ELSE IF (FlowEl(iloc)%GenRe >= FlowEl(iloc)%ReCritTurb) THEN ! turbulent flow | |||||
FlowEl(iloc)%FricToQPartialDiff = FlowEl(iloc)%FricPressLoss / FlowEl(iloc)%FlowRate & | |||||
* (2. - FlowEl(iloc)%b * (2. - FlowEl(iloc)%nIndex)) | |||||
ELSE ! transition from laminar to turbulent | |||||
FlowEl(iloc)%FricToQPartialDiff = FlowEl(iloc)%FricPressLoss / FlowEl(iloc)%FlowRate & | |||||
* (2. + (2. - FlowEl(iloc)%nIndex) & | |||||
* ((FlowEl(iloc)%a * FlowEl(iloc)%GenRe**(1. - FlowEl(iloc)%b) - 16.) / 800. / FlowEl(iloc)%f - 1.)) | |||||
END IF | |||||
ELSE IF (MudProperties%ActiveRheologyModel == Bingham_RheologyModel) THEN ! Bingham Plastic | |||||
IF (FlowEl(iloc)%GenRe <= 2000.0 .OR. FlowEl(iloc)%f == 0.0) THEN ! laminar flow if f = 0.0, we have no flow in first time flowing | |||||
FlowEl(iloc)%FricToQPartialDiff = (16. * FlowEl(iloc)%muPlastic * REAL(FlowEl(iloc)%Length) * 2.224 * (10.)**(-3)) & | |||||
/ (25.81 * 928. * (1 - 0.184 * FlowEl(iloc)%alpha) * FlowEl(iloc)%Dhyd**2 * FlowEl(iloc)%Area) | |||||
ELSE IF (FlowEl(iloc)%GenRe >= 4000.0) THEN ! turbulent flow | |||||
FlowEl(iloc)%FricToQPartialDiff = FlowEl(iloc)%FricPressLoss / FlowEl(iloc)%FlowRate & | |||||
* (2. - FlowEl(iloc)%b * (2. - FlowEl(iloc)%muPlastic / FlowEl(iloc)%mueff)) | |||||
ELSE ! transition from laminar to turbulent | |||||
FlowEl(iloc)%FricToQPartialDiff = FlowEl(iloc)%FricPressLoss / FlowEl(iloc)%FlowRate & | |||||
* (2. + (2. - FlowEl(iloc)%muPlastic / FlowEl(iloc)%mueff) & | |||||
* ((FlowEl(iloc)%a * FlowEl(iloc)%GenRe**(1. - FlowEl(iloc)%b) - 16.) / 2000. / FlowEl(iloc)%f - 1.)) | |||||
END IF | |||||
END IF | |||||
END IF | |||||
IF (FlowEl(iloc)%FricToQPartialDiff < 0.0) THEN | |||||
!WRITE (*,*) ' iloc, Re, FricPressLoss, FricToQPartialDiff' , iloc, FlowEl(iloc)%GenRe, FlowEl(iloc)%FricPressLoss, FlowEl(iloc)%FricToQPartialDiff | |||||
!CALL ERRORSTOP('Error in Calculating FricToQPartialDiff') | |||||
END IF | |||||
END SUBROUTINE PartialDerivativeFricToFlowRate |
@@ -0,0 +1,799 @@ | |||||
SUBROUTINE PressureHorizAndStringDistribution | |||||
!! Record of revisions | |||||
!! Date Programmer Discription of change | |||||
!! ------ ------------ ----------------------- | |||||
!! 1396/07/30 Sheikh Original code | |||||
!! | |||||
USE FricPressDropVarsModule | |||||
use PressureDisplayVARIABLESModule | |||||
USE MudSystemVARIABLES | |||||
USE GeoElements_FluidModule | |||||
USE Fluid_Flow_Startup_Vars | |||||
use KickVARIABLESModule | |||||
USE CMudPropertiesVariables | |||||
USE CDataDisplayConsoleVariables !, StandPipePressureDataDisplay=> ChokeControlPanel%StandPipePressure | |||||
USE CDataDisplayConsoleVariables !, CasingPressureDataDisplay=> CasingPressure | |||||
USE CDrillWatchVariables | |||||
USE CShoeVariables | |||||
USE CDownHoleVariables! , OperationScenarioCommon%ElevatorConnection => DownHole%CasingPressure | |||||
USE TD_WellGeometry | |||||
USE CManifolds | |||||
USE VARIABLES | |||||
USE CError | |||||
use UTUBEVARSModule | |||||
USE CKellyConnectionEnumVariables | |||||
USE Pumps_VARIABLES | |||||
USE , INTRINSIC :: IEEE_ARITHMETIC | |||||
Use TD_DrillStemComponents | |||||
Use sROP_Variables | |||||
IMPLICIT NONE | |||||
INTEGER :: i , j , l | |||||
INTEGER :: ifric | |||||
INTEGER :: OldCasingPressure | |||||
REAL :: PressBelowFloatValve , PressAboveFloatValve ![psi] | |||||
REAL :: PumpMinDischargedVol = 0.0050 ! [gal] | |||||
REAL :: FloatValveBottomToUpAreaRatio = 1.1 ![-] | |||||
REAL :: ZeroHeight , StaticHeadOnBit | |||||
REAL(8) :: ShoeTVD | |||||
!REAL(8) , DIMENSION(5) :: MDObserve , TVDObserve , StPressObserve , AnnPressObserve , NomMD | |||||
ExitMass = 0.0 | |||||
BitPressLoss = 0.0 | |||||
WellHeadWasOpen = WellHeadOpen | |||||
WellToChokeManifoldWasOpen = MudSystem%WellToChokeManifoldOpen | |||||
KickWasExitingThroughChoke = .FALSE. | |||||
IF (MudSystem%UtubeMode1Activated .OR. FloatValveWasOpen == .FALSE.) THEN ! Horizontal line flow rate | |||||
FlowEl(1 : NoHorizontalEl)%FlowRate = 0.0 | |||||
ELSE ! connection and line is open | |||||
FlowEl(1 : NoHorizontalEl)%FlowRate = MudSystem%StringFlowRate ! pump flow rate [gpm] | |||||
END IF | |||||
!WRITE (*,*) 'a)A/B P Bit', StaticHeadOnBit , FlowEl(AnnulusFirstEl)%StartPress , SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) | |||||
!IF (FloatValveIn == .FALSE.) FloatValveOpen = .TRUE. | |||||
FloatValveWasOpen = FloatValveOpen | |||||
PressBelowFloatValve = FlowEl(AnnulusFirstEl)%StartPress | |||||
StMudVol = SUM(FlowEl(1 : StringLastEl)%Volume) * Convft3toUSGal | |||||
StDeltaPtoDeltaVCompressibility = 1.0 / (MudCompressibility * StMudVol) | |||||
AnnMudVol = SUM(FlowEl(AnnulusFirstEl : NumbEl)%Volume) * Convft3toUSGal | |||||
!StCompressedMudVol = StCompressedMudVol + REAL(St_Saved_MudDischarged_Volume_Final) | |||||
!WRITE (*,*) 'St_Saved_MudDischarged_Volume_Final', REAL(St_Saved_MudDischarged_Volume_Final) | |||||
!StDeltaPDueToCompressibility = StCompressedMudVol / (MudCompressibility * StMudVol) | |||||
!PressAboveFloatValve = StDeltaPDueToCompressibility + SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) !!FlowEl(StringLastEl)%EndPress | |||||
!IF (NoGasPocket > 0) THEN ! mud exprience no comressibility | |||||
!IF (KickVolume > 2.0) THEN | |||||
IF ( (DownHole%KickVolume > 2.0) .or. (NoGasPocket>1) .or. (any(FlowEl(OpenholeFirstEl:NumbEl)%Materialtype==1)) .or. (ROP_bit%RateofPenetration > 0.0) ) THEN | |||||
AnnCompressedMudVol = 0.0 | |||||
AnnDeltaPDueToCompressibility = 0.0 | |||||
ELSE IF (WellHeadOpen) THEN | |||||
AnnDeltaPtoDeltaVCompressibility = 1.0 / (MudCompressibility * AnnMudVol) | |||||
AnnCompressedMudVol = BackPressure / AnnDeltaPtoDeltaVCompressibility | |||||
AnnDeltaPDueToCompressibility = AnnCompressedMudVol / (MudCompressibility * AnnMudVol) | |||||
ELSE ! No gas pocket, wellhead is closed and mud is compressed based on volume pumped into annulus | |||||
AnnDeltaPtoDeltaVCompressibility = 1.0 / (MudCompressibility * AnnMudVol) | |||||
AnnCompressedMudVol = AnnCompressedMudVol + REAL(MudSystem%Ann_Saved_MudDischarged_Volume_Final) !!!!!!!!! | |||||
AnnCompressedMudVol = MAX((AnnCompressedMudVol - REAL(MudSystem%Qlost / ConvMinToSec / dt)) , 0.0) | |||||
AnnDeltaPDueToCompressibility = AnnCompressedMudVol / (MudCompressibility * AnnMudVol) | |||||
END IF | |||||
IF (FloatValveIn == .FALSE. .OR. NoGasPocket == 0 .OR. (FloatValveWasOpen .AND. REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) >= PumpMinDischargedVol)) THEN ! float valve remains open | |||||
FloatValveOpen = .TRUE. | |||||
FlowEl(StringFirstEl : StringLastEl)%FlowRate = REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) / dt * ConvMinToSec !MudSystem%StringFlowRate ! String flow rate pump flow rate [gpm] | |||||
!!!!!!!!!!!!!!! Calculating frictional pressure loss | |||||
IF (WellHeadOpen) THEN | |||||
DO ifric = 1 , StringLastEl | |||||
CALL FricPressDrop(ifric) | |||||
!WRITE (*,*) ' element No, FlowRate , Density, FricPressLoss', ifric, FlowEl(ifric)%FlowRate, FlowEl(ifric)%Density, FlowEl(ifric)%FricPressLoss | |||||
IF (IEEE_IS_NaN(FlowEl(ifric)%FricPressLoss)) THEN | |||||
WRITE (*,*) 'Hz/St start, end, density, Q, mu, Type' , FlowEl(ifric)%StartX, FlowEl(ifric)%EndX, FlowEl(ifric)%Density, FlowEl(ifric)%FlowRate, FlowEl(ifric)%mueff, FlowEl(ifric)%MaterialType | |||||
CALL ErrorStop('NaN in calculating pressure drop' , ifric) | |||||
END IF | |||||
END DO | |||||
END IF | |||||
!!!!!!!!!!!!!!! | |||||
!IF (ABS(MudVolume_InjectedToBH - St_Saved_MudDischarged_Volume_Final)> PumpMinDischargedVol) WRITE (*,*) 'Injected to BH & St Saved Mud', MudVolume_InjectedToBH , St_Saved_MudDischarged_Volume_Final | |||||
IF (BitTotallyPluged) THEN | |||||
MudSystem%MudVolume_InjectedToBH = 0.d0 | |||||
StCompressedMudVol = StCompressedMudVol + REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) | |||||
StDeltaPDueToCompressibility = StCompressedMudVol * StDeltaPtoDeltaVCompressibility | |||||
ELSE IF (WellHeadOpen .OR. NoGasPocket > 0) THEN | |||||
IF (REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) >= PumpMinDischargedVol) THEN | |||||
MudSystem%MudVolume_InjectedToBH = MudSystem%St_Saved_MudDischarged_Volume_Final | |||||
!WRITE (*,*) 'MudVolume_InjectedToBH,BitTrue', MudVolume_InjectedToBH | |||||
!IF (BitTrue .AND. UtubeMode1Activated == .FALSE.) THEN | |||||
IF (BitTrue) THEN | |||||
BitPressLoss = KBit * (MudSystem%MudVolume_InjectedToBH * ConvMinToSec / dt)**2 | |||||
!WRITE (*,*) 'BitPressLoss', BitPressLoss | |||||
END IF | |||||
StCompressedMudVol = BitPressLoss / StDeltaPtoDeltaVCompressibility | |||||
ELSE | |||||
MudSystem%MudVolume_InjectedToBH = MAX( 0.d0 , REAL((StDeltaPDueToCompressibility + SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff - PressBelowFloatValve - AnnDeltaPDueToCompressibility - FloatValveMinOpenPressure) & | |||||
/ StDeltaPtoDeltaVCompressibility ) * 1.d0)) | |||||
MudSystem%MudVolume_InjectedToBH = MIN(MudSystem%MudVolume_InjectedToBH , StCompressedMudVol) | |||||
StCompressedMudVol = StCompressedMudVol - MudSystem%MudVolume_InjectedToBH | |||||
END IF | |||||
StDeltaPDueToCompressibility = StCompressedMudVol / (MudCompressibility * StMudVol) | |||||
ELSE ! IF (NoGasPocket == 0 .AND. WellHeadOpen == .FALSE.) THEN | |||||
StCompressedMudVol = StCompressedMudVol + REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) | |||||
StDeltaPDueToCompressibility = StCompressedMudVol * StDeltaPtoDeltaVCompressibility | |||||
MudSystem%MudVolume_InjectedToBH = MAX( 0.d0 , REAL((StDeltaPDueToCompressibility - AnnDeltaPDueToCompressibility - FloatValveMinOpenPressure) & | |||||
/ (StDeltaPtoDeltaVCompressibility + AnnDeltaPtoDeltaVCompressibility)) * 1.d0) | |||||
MudSystem%MudVolume_InjectedToBH = MIN(MudSystem%MudVolume_InjectedToBH , StCompressedMudVol) | |||||
StCompressedMudVol = StCompressedMudVol - REAL(MudSystem%MudVolume_InjectedToBH) | |||||
StDeltaPDueToCompressibility = StCompressedMudVol / (MudCompressibility * StMudVol) | |||||
FlowEl(AnnulusFirstEl : NumbEl)%StartPress = FlowEl(AnnulusFirstEl : NumbEl)%StartPress + StDeltaPDueToCompressibility | |||||
FlowEl(AnnulusFirstEl : NumbEl)%EndPress = FlowEl(AnnulusFirstEl : NumbEl)%EndPress + StDeltaPDueToCompressibility | |||||
!WRITE (*,*) 'WellHeadOpen', WellHeadOpen | |||||
!WRITE (*,*) ' StCompressedMudVol, StDeltaPDueToCompressibility',StCompressedMudVol, StDeltaPDueToCompressibility | |||||
!WRITE (*,*) ' AnnCompressedMudVol, AnnDeltaPDueToCompressibility',AnnCompressedMudVol, AnnDeltaPDueToCompressibility | |||||
END IF | |||||
FlowEl(StringLastEl)%EndPress = FlowEl(AnnulusFirstEl)%StartPress + BitPressLoss + FloatValveMinOpenPressure | |||||
!WRITE (*,*) 'BitPressLoss=', BitPressLoss | |||||
FlowEl(StringLastEl)%StartPress = FlowEl(StringLastEl)%EndPress + FlowEl(StringLastEl)%FricPressLoss - FlowEl(StringLastEl)%StaticPressDiff | |||||
DO i = StringLastEl - 1 , StringFirstEl , -1 | |||||
FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
FlowEl(i)%StartPress = FlowEl(i)%EndPress + FlowEl(i)%FricPressLoss - FlowEl(i)%StaticPressDiff | |||||
!WRITE(*,*) "STRING: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
!WRITE(*,*) "STRING: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
END DO | |||||
!FlowEl(NoHorizontalEl)%EndPress = FlowEl(StringFirstEl)%StartPress - FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
!WRITE (*,*) '- FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD1=', - FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
!FlowEl(NoHorizontalEl)%StartPress = FlowEl(NoHorizontalEl)%EndPress + FlowEl(StringLastEl)%FricPressLoss | |||||
!DO i = NoHorizontalEl - 1 , 1 , -1 | |||||
! FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
! FlowEl(i)%StartPress = FlowEl(i)%EndPress + FlowEl(i)%FricPressLoss | |||||
! !WRITE(*,*) "HORIZONTAL: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
! !WRITE(*,*) "HORIZONTAL: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
!END DO | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!! Float valve was open and remains open | |||||
ELSE IF (REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) < PumpMinDischargedVol) THEN ! NoGasPocket > 0 | |||||
FloatValveOpen = FloatValveWasOpen ! remains in its former status | |||||
IF (FloatValveOpen) THEN | |||||
PressAboveFloatValve = MAX(FlowEl(AnnulusFirstEl)%StartPress , SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) + 0.052 * FlowEl(StringFirstEl)%Density * FlowEl(StringFirstEl)%StartTVD) | |||||
ELSE | |||||
PressAboveFloatValve = SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) + StDeltaPDueToCompressibility | |||||
MudSystem%MudVolume_InjectedToBH = 0.d0 | |||||
END IF | |||||
IF (PressBelowFloatValve >= PressAboveFloatValve .AND. KickFlux) THEN | |||||
FloatValveOpen = .FALSE. | |||||
IF (FloatValveOpen /= FloatValveWasOpen) THEN ! float valve was open and now closed | |||||
WRITE (*,*) 'Float valve was open and now closed' | |||||
WRITE (*,*) 'PressAboveFloatValve=', PressAboveFloatValve | |||||
WRITE (*,*) 'PressBelowFloatValve=', PressBelowFloatValve | |||||
END IF | |||||
END IF | |||||
IF (FloatValveOpen) THEN | |||||
MudSystem%MudVolume_InjectedToBH = MAX( 0.d0 , 0.1 * REAL((PressAboveFloatValve - PressBelowFloatValve - AnnDeltaPDueToCompressibility - FloatValveMinOpenPressure) & | |||||
/ StDeltaPtoDeltaVCompressibility ) * 1.d0) | |||||
MudSystem%MudVolume_InjectedToBH = MIN(MudSystem%MudVolume_InjectedToBH , StCompressedMudVol) | |||||
!WRITE (*,*) 'MudVolume_InjectedToBH (No Pump)', MudVolume_InjectedToBH | |||||
StCompressedMudVol = StCompressedMudVol - MudSystem%MudVolume_InjectedToBH | |||||
StDeltaPDueToCompressibility = StCompressedMudVol / (MudCompressibility * StMudVol) | |||||
!WRITE (*,*) 'StDeltaPDueToCompressibility(No Pump)', StDeltaPDueToCompressibility | |||||
END IF | |||||
IF (NoGasPocket == 0 .AND. WellHeadOpen == .FALSE.) THEN !*********** | |||||
FlowEl(AnnulusFirstEl : NumbEl)%StartPress = FlowEl(AnnulusFirstEl : NumbEl)%StartPress + AnnDeltaPDueToCompressibility | |||||
FlowEl(AnnulusFirstEl : NumbEl)%EndPress = FlowEl(AnnulusFirstEl : NumbEl)%EndPress + AnnDeltaPDueToCompressibility | |||||
END IF | |||||
IF (FloatValveOpen) THEN | |||||
FlowEl(StringLastEl)%EndPress = MAX(FlowEl(AnnulusFirstEl)%StartPress , SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) + 0.052 * FlowEl(StringFirstEl)%Density * FlowEl(StringFirstEl)%StartTVD) | |||||
ELSE | |||||
FlowEl(StringLastEl)%EndPress = StDeltaPDueToCompressibility + SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) | |||||
END IF | |||||
FlowEl(StringLastEl)%StartPress = FlowEl(StringLastEl)%EndPress - FlowEl(StringLastEl)%StaticPressDiff | |||||
DO i = StringLastEl - 1 , StringFirstEl , -1 | |||||
FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
FlowEl(i)%StartPress = FlowEl(i)%EndPress + FlowEl(i)%FricPressLoss - FlowEl(i)%StaticPressDiff | |||||
!WRITE(*,*) "STRING: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
!WRITE(*,*) "STRING: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
END DO | |||||
!FlowEl(NoHorizontalEl)%EndPress = FlowEl(StringFirstEl)%StartPress - FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
!WRITE (*,*) '- FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD2=', - FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
!FlowEl(NoHorizontalEl)%StartPress = FlowEl(NoHorizontalEl)%EndPress + FlowEl(StringLastEl)%FricPressLoss | |||||
!DO i = NoHorizontalEl - 1 , 1 , -1 | |||||
! FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
! FlowEl(i)%StartPress = FlowEl(i)%EndPress + FlowEl(i)%FricPressLoss | |||||
! !WRITE(*,*) "HORIZONTAL: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
! !WRITE(*,*) "HORIZONTAL: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
!END DO | |||||
!WRITE (*,*) ' StCompressedMudVol, StDeltaPDueToCompressibility',StCompressedMudVol, StDeltaPDueToCompressibility | |||||
!WRITE (*,*) ' AnnCompressedMudVol, AnnDeltaPDueToCompressibility',AnnCompressedMudVol, AnnDeltaPDueToCompressibility | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!! Float valve was open (close) and maybe remains open (close) or maybe closed | |||||
ELSE IF(FloatValveWasOpen == .FALSE. .AND. REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) >= PumpMinDischargedVol) THEN | |||||
FloatValveOpen = .FALSE. | |||||
MudSystem%MudVolume_InjectedToBH = 0.d0 | |||||
StCompressedMudVol = StCompressedMudVol + REAL(MudSystem%St_Saved_MudDischarged_Volume_Final) | |||||
StDeltaPDueToCompressibility = StCompressedMudVol * StDeltaPtoDeltaVCompressibility | |||||
PressAboveFloatValve = SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) + StDeltaPDueToCompressibility | |||||
IF (PressAboveFloatValve > FloatValveBottomToUpAreaRatio * PressBelowFloatValve) THEN ! float valve was open and now closed | |||||
FloatValveOpen = .TRUE. | |||||
WRITE (*,*) 'Float valve was closed and now opened' | |||||
WRITE (*,*) 'PressAboveFloatValve=', PressAboveFloatValve | |||||
WRITE (*,*) 'PressBelowFloatValve=', PressBelowFloatValve | |||||
END IF | |||||
FlowEl(StringLastEl)%EndPress = PressAboveFloatValve | |||||
FlowEl(StringLastEl)%StartPress = FlowEl(StringLastEl)%EndPress - FlowEl(StringLastEl)%StaticPressDiff | |||||
DO i = StringLastEl - 1 , StringFirstEl , -1 | |||||
FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
FlowEl(i)%StartPress = FlowEl(i)%EndPress - FlowEl(i)%StaticPressDiff | |||||
!WRITE(*,*) "STRING: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
!WRITE(*,*) "STRING: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
END DO | |||||
END IF | |||||
IF ((MudSystem%UtubePossibility == .TRUE. .AND. Get_KellyConnection() /= KELLY_CONNECTION_STRING) .OR. MudSystem%NewPipeFilling == 0) THEN | |||||
FlowEl(NoHorizontalEl)%EndPress = 0.0 | |||||
ELSE IF (WellHeadOpen == .FALSE.) THEN | |||||
FlowEl(NoHorizontalEl)%EndPress = FlowEl(StringFirstEl)%StartPress - 0.052 * FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
!WRITE (*,*) 'Density , StartX= , StartPress', FlowEl(NoHorizontalEl)%Density , FlowEl(StringFirstEl)%StartTVD | |||||
ELSE IF (WellHeadOpen) THEN | |||||
FlowEl(NoHorizontalEl)%EndPress = FlowEl(StringFirstEl)%StartPress - 2.0 * 0.052 * FlowEl(NoHorizontalEl)%Density * FlowEl(StringFirstEl)%StartTVD | |||||
END IF | |||||
FlowEl(NoHorizontalEl)%StartPress = FlowEl(NoHorizontalEl)%EndPress + FlowEl(NoHorizontalEl)%FricPressLoss | |||||
DO i = NoHorizontalEl - 1 , 1 , -1 | |||||
FlowEl(i)%EndPress = FlowEl(i + 1)%StartPress | |||||
FlowEl(i)%StartPress = FlowEl(i)%EndPress + FlowEl(i)%FricPressLoss | |||||
!WRITE(*,*) "HORIZONTAL: Start , End Pressure", FlowEl(i)%StartPress , FlowEl(i)%EndPress | |||||
!WRITE(*,*) "HORIZONTAL: Start , End X", FlowEl(i)%StartX , FlowEl(i)%EndX | |||||
END DO | |||||
!WRITE (*,*) 'MudVolume_InjectedToBH==', MudVolume_InjectedToBH | |||||
!WRITE (*,*) 'Ann_Saved_MudDischarged_Volume_Final==', Ann_Saved_MudDischarged_Volume_Final | |||||
!!!!!!!!!!!!!!!!!!!!! Pressure distribution in string and horizontal pump to string line | |||||
IF (RamLine%ShearBop_Situation_forTD == 1) THEN | |||||
FlowEl(1 : NoHorizontalEl)%EndPress = 0.0 | |||||
FlowEl(1 : NoHorizontalEl)%StartPress = 0.0 | |||||
FlowEl(1 : NoHorizontalEl)%FricPressLoss = 0.0 | |||||
END IF | |||||
!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!IF (NoGasPocket == 0 .AND. WellHeadOpen) THEN | |||||
! FlowEl(1 : NoHorizontalEl + NoStringEl)%EndPress = FlowEl(1 : NoHorizontalEl + NoStringEl)%EndPress + StDeltaPDueToCompressibility + AnnDeltaPDueToCompressibility | |||||
! FlowEl(1 : NoHorizontalEl + NoStringEl)%StartPress = FlowEl(1 : NoHorizontalEl + NoStringEl)%StartPress + StDeltaPDueToCompressibility + AnnDeltaPDueToCompressibility | |||||
! FlowEl(NoHorizontalEl + NoStringEl +1 : NumbEl)%EndPress = FlowEl(NoHorizontalEl + NoStringEl +1 : NumbEl)%EndPress + AnnDeltaPDueToCompressibility | |||||
! FlowEl(NoHorizontalEl + NoStringEl + 1 : NumbEl)%StartPress = FlowEl(NoHorizontalEl + NoStringEl + 1 : NumbEl)%StartPress + AnnDeltaPDueToCompressibility | |||||
!ELSE | |||||
!IF (NoGasPocket == 0 .AND. WellHeadOpen == .FALSE.) THEN | |||||
! FlowEl(1 : StringLastEl)%EndPress = FlowEl(1 : StringLastEl)%EndPress + StDeltaPDueToCompressibility + 30.0 ! badan eslah shavad | |||||
! FlowEl(1 : StringLastEl)%StartPress = FlowEl(1 : NoHorizontalEl + NoStringEl)%StartPress + StDeltaPDueToCompressibility + 30.0 | |||||
! FlowEl(AnnulusFirstEl : NumbEl)%EndPress = FlowEl(AnnulusFirstEl : NumbEl)%EndPress + AnnDeltaPDueToCompressibility | |||||
! FlowEl(AnnulusFirstEl : NumbEl)%StartPress = FlowEl(AnnulusFirstEl : NumbEl)%StartPress + AnnDeltaPDueToCompressibility | |||||
!END IF | |||||
IF (MudSystem%UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadOpen) THEN | |||||
MudSystem%MudVolume_InjectedToBH = 0.d0 | |||||
MudSystem%MudVolume_InjectedFromAnn = 0.d0 | |||||
!ELSE | |||||
! | |||||
! IF (FloatValveOpen .AND. WellHeadOpen .AND. NoGasPocket == 0) THEN | |||||
! MudVolume_InjectedToBH = MAX( 0.d0 , REAL((StDeltaPDueToCompressibility - FloatValveMinOpenPressure) / StDeltaPtoDeltaVCompressibility) * 1.d0) | |||||
! !MudSystem%MudVolume_InjectedFromAnn = Ann_Saved_MudDischarged_Volume_Final !REAL((AnnDeltaPDueToCompressibility - BackPressure) / AnnDeltaPtoDeltaVCompressibility) * 1.d0 | |||||
! !WRITE (*,*) 'Pressure above/under bit', FlowEl(NoHorizontalEl + NoStringEl)%EndPress, FlowEl(1 + NoHorizontalEl + NoStringEl)%StartPress | |||||
! IF (MudVolume_InjectedToBH <= 0) MudVolume_InjectedToBH = 0.d0 | |||||
! !IF (MudSystem%MudVolume_InjectedFromAnn <= 0) MudSystem%MudVolume_InjectedFromAnn = 0.d0 | |||||
! ELSE IF (FloatValveOpen .AND. WellHeadOpen == .FALSE. .AND. NoGasPocket == 0) THEN | |||||
! MudVolume_InjectedToBH = MAX( 0.d0 , REAL((PressAboveFloatValve + StDeltaPDueToCompressibility - AnnDeltaPDueToCompressibility - PressBelowFloatValve - FloatValveMinOpenPressure) & | |||||
! / (StDeltaPtoDeltaVCompressibility - AnnDeltaPtoDeltaVCompressibility)) * 1.d0) | |||||
! MudSystem%MudVolume_InjectedFromAnn = 0.d0 | |||||
! ELSE IF (FloatValveOpen .AND. WellHeadOpen .AND. NoGasPocket > 0) THEN | |||||
! MudVolume_InjectedToBH = MAX( 0.d0 , REAL((PressAboveFloatValve + StDeltaPDueToCompressibility - PressBelowFloatValve - FloatValveMinOpenPressure) / StDeltaPtoDeltaVCompressibility) * 1.d0) | |||||
! ! MudSystem%MudVolume_InjectedFromAnn = REAL(Ann_Saved_MudDischarged_Volume_Final) * 1.d0 | |||||
! ELSE IF (FloatValveOpen .AND. WellHeadOpen == .FALSE. .AND. NoGasPocket > 0) THEN | |||||
! MudVolume_InjectedToBH = MAX( 0.d0 , REAL((PressAboveFloatValve + StDeltaPDueToCompressibility - AnnDeltaPDueToCompressibility - PressBelowFloatValve - FloatValveMinOpenPressure) & | |||||
! / (StDeltaPtoDeltaVCompressibility - AnnDeltaPtoDeltaVCompressibility)) * 1.d0) | |||||
! MudSystem%MudVolume_InjectedFromAnn = 0.d0 | |||||
! END IF | |||||
!StCompressedMudVol = MAX(StCompressedMudVol - REAL(MudVolume_InjectedToBH) , 0.0) | |||||
!AnnCompressedMudVol = MAX(AnnCompressedMudVol - REAL(MudSystem%MudVolume_InjectedFromAnn) , 0.0) | |||||
!StDeltaPDueToCompressibility = StCompressedMudVol / (MudCompressibility * StMudVol) | |||||
!AnnDeltaPDueToCompressibility = AnnCompressedMudVol / (MudCompressibility * AnnMudVol) | |||||
END IF | |||||
!MudVolume_InjectedToBH = 0.0 | |||||
!MudVolume_InjectedToBH = St_Saved_MudDischarged_Volume_Final | |||||
!WRITE (*,*) 'CompMudVol, DeltaP, MudVolumeInjected' | |||||
!WRITE (*,*) StCompressedMudVol, StDeltaPDueToCompressibility, REAL(MudVolume_InjectedToBH) | |||||
!WRITE (*,*) AnnCompressedMudVol, AnnDeltaPDueToCompressibility, REAL(MudSystem%MudVolume_InjectedFromAnn) | |||||
!WRITE (*,*) 'Press above/Below Float valve ', FlowEl(NoHorizontalEl + NoStringEl)%EndPress , FlowEl(NoHorizontalEl + NoStringEl + 1)%StartPress | |||||
!write(*,*) 'MudSystem%MudVolume_InjectedFromAnn***=' , MudSystem%MudVolume_InjectedFromAnn, Ann_Saved_MudDischarged_Volume_Final | |||||
110 FORMAT (I6 , 4X , F6.2 , 7X , F4.2 , 3X , F4.1 , 2X , F4.2) | |||||
!DO i = NumbEl , NumbEl - NoOpenHoleEl + 1 , -1 ! op elements | |||||
! WRITE (*,*) 'el no, start, end' , i, FlowEl(i)%StartPress, FlowEl(i)%EndPress | |||||
!END DO | |||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | |||||
!!!! Kick Information Reports | |||||
!!!!!!!!!!!!!!!!! 1- Stand pipe pressure gauge PressureGauges(1) | |||||
!ElementTrueDepth = STpipeGauge_Height/Convfttom | |||||
!DistancetoRefrence = -170.7 ! 165 ft after pump and 100 ft before string | |||||
i = 1 | |||||
DO WHILE (NOT(FlowEl(i)%EndX >= -170 .AND. FlowEl(i)%StartX <= -170)) | |||||
i = i + 1 | |||||
IF (i > NoHorizontalEl) EXIT | |||||
END DO | |||||
CALL PumpPressureDelay%AddToFirst(REAL(FlowEl(i)%StartPress - 0.052 * (MudSystem%STpipeGauge_Height / Convfttom) * FlowEl(i)%Density + (FlowEl(i)%StartX + 170) * FlowEl(i)%dPdLFric)) | |||||
CALL PumpPressureDelay%Remove(PressureTimeStepDelay(1) + 1) | |||||
!IF (ANY(PUMP(:)%PowerFailMalf == 1)) PumpPressureDelay%Array(1 : PressureTimeStepDelay(1) / 2) = 0.0 !seyyed goft vaghti pumpfailure mishavad feshar dasti 0 nashavad, be in dalil in khat comment shod. | |||||
DO j = PressureTimeStepDelay(1) , 1 , -1 | |||||
IF (NOT(IEEE_IS_NaN(PumpPressureDelay%Array(j)))) THEN | |||||
PressureGauges(1) = INT(PumpPressureDelay%Array(j)) | |||||
EXIT | |||||
END IF | |||||
END DO | |||||
!PressureGauges(1) = INT(PumpPressureDelay%Array(PressureTimeStepDelay(1))) | |||||
IF (i > NoHorizontalEl) THEN | |||||
WRITE (*,*) ' Error in calculating standpipe pressure ' | |||||
END IF | |||||
IF (PressureGauges(1) < 0) THEN | |||||
!CALL Set_StandPipePressure(real(PressureGauges(1) , 8)) ! for display console | |||||
PressureGauges(1) = 0.0 | |||||
!CALL Set_StandPipePressure(0.0d0) !StandPipePressureGauge = 0 | |||||
END IF | |||||
DownHole%DrillPipePressure = real(PressureGauges(1), 8) | |||||
!WRITE (*,*) 'Drillpipe Pressure', PressureGauges(1) | |||||
!!!!!!!!!!!!!!!!! 2- Casing pressure gauge PressureGauge(2) | |||||
!WRITE (*,*) 'here 1', (WelltoPitsOpen == .FALSE. .AND. WellToChokeManifoldOpen) , (Valve(26)%Status == .TRUE. .AND. Valve(47)%Status == .TRUE. .AND. Valve(49)%Status == .TRUE.), BackPressure | |||||
!WRITE (*,*) Valve(26)%Status , Valve(47)%Status , Valve(49)%Status | |||||
!WRITE (*,*) (Valve(26)%Status == .TRUE.) , (Valve(47)%Status == .TRUE.) , (Valve(49)%Status == .TRUE.) | |||||
!!! in normal mode changes in choke position immidiately observes in casing pressure | |||||
!! but when pumps off due to failure, casing pressure will drop after a delay time | |||||
IF (MudSystem%WellToChokeManifoldOpen .OR. MudSystem%WellToChokeLineGauge) THEN | |||||
!WRITE (*,*) 'Here 1' | |||||
CALL CasingPressureDelay%AddToFirst(FlowEl(NoHorizontalEl + NoStringEl + NoAnnulusEl + NoWellToChokeEl)%EndPress) | |||||
CALL CasingPressureDelay%Remove(PressureTimeStepDelay(1) + 1) | |||||
DO j = 1 , PressureTimeStepDelay(1) | |||||
IF (NOT(IEEE_IS_NaN(CasingPressureDelay%Array(j)))) THEN | |||||
PressureGauges(2) = INT(CasingPressureDelay%Array(j)) | |||||
EXIT | |||||
END IF | |||||
END DO | |||||
!PressureGauges(2) = INT(CasingPressureDelay%Array(1)) | |||||
IF (ANY(PUMP(:)%PowerFailMalf == 1)) THEN | |||||
DO j = PressureTimeStepDelay(1) , 1 , -1 | |||||
IF (NOT(IEEE_IS_NaN(CasingPressureDelay%Array(j)))) THEN | |||||
PressureGauges(2) = INT(CasingPressureDelay%Array(j)) | |||||
EXIT | |||||
END IF | |||||
END DO | |||||
END IF | |||||
!IF (ANY(PUMP(:)%PowerFailMalf == 1)) PressureGauges(2) = INT(CasingPressureDelay%Array(PressureTimeStepDelay(1))) | |||||
ELSE !IF (ChokeLineGaugeToTanks) THEN | |||||
PressureGauges(2) = 0 | |||||
!WRITE (*,*) 'Here 2' | |||||
END IF | |||||
!WRITE (*,*) 'GaugePoint(2)%Pressure =' , GaugePoint(2)%Pressure | |||||
!IF (PressureGauges(2) < 0) THEN | |||||
! PressureGauges(2) = 0.0 | |||||
!END IF | |||||
CALL Set_CasingPressure(real(PressureGauges(2) , 8)) ! for display console | |||||
Downhole%CasingPressure = real(PressureGauges(2) , 8) | |||||
!IF (PressureGauges(2) > 3000.0) THEN | |||||
! !CALL Error(' High Casing Pressure') | |||||
!END IF | |||||
!WRITE (*,*) 'Casing Pressure=' , PressureGauges(2) | |||||
!!!!!!!!!!!!!!!!! 3- Bottom Hole Pressure PressureGauge(3) | |||||
CALL BottomHolePressureDelay%AddToFirst(FlowEl(OpenholeFirstEl)%StartPress) | |||||
CALL BottomHolePressureDelay%Remove(PressureTimeStepDelay(2) + 1) | |||||
!PressureGauges(3) = INT(BottomHolePressureDelay%Array(PressureTimeStepDelay(2))) | |||||
DO j = PressureTimeStepDelay(2) , 1 , -1 | |||||
IF (NOT(IEEE_IS_NaN(BottomHolePressureDelay%Array(j)))) THEN | |||||
PressureGauges(3) = INT(BottomHolePressureDelay%Array(j)) | |||||
EXIT | |||||
END IF | |||||
END DO | |||||
BottomHolePress = BottomHolePressureDelay%Array(PressureTimeStepDelay(2)) | |||||
DownHole%BottomHolePressure = REAL(PressureGauges(3) , 8) | |||||
!!!!!!!!!!!!!!!!! 4- Under Bit Pressure PressureGauges(4) | |||||
PressureGauges(4) = FlowEl(AnnulusFirstEl)%StartPress | |||||
!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!!!!!!!!!! 5- Casing Shoe Pressure PressureGauges(5) | |||||
!IF (ShoeDepth <= FlowEl(NoHorizontalEl + NoStringEl + 1)%StartX) THEN | |||||
DO ShoeFlowElNo = AnnulusFirstEl , NumbEl | |||||
IF (FlowEl(ShoeFlowElNo)%StartX >= Shoe%ShoeDepth .AND. FlowEl(ShoeFlowElNo)%EndX < Shoe%ShoeDepth) EXIT | |||||
END DO | |||||
CALL TVD_Calculator(Shoe%ShoeDepth , ShoeTVD) | |||||
IF (ShoeFlowElNo > NumbEl) THEN | |||||
WRITE (*,*) 'ShoeDepth =', Shoe%ShoeDepth | |||||
DO i = AnnulusFirstEl , NumbEl | |||||
WRITE (*,*) 'i, StartX, EndX', i, FlowEl(i)%StartX, FlowEl(i)%EndX | |||||
END DO | |||||
CALL ErrorSTOP ('Error in finding location of shoe') | |||||
END IF | |||||
!ELSE | |||||
! WRITE (*,*) ' Error in calculating shoe pressure ' | |||||
!END IF | |||||
CALL ShoePressureDelay%AddToFirst(REAL(FlowEl(ShoeFlowElNo)%StartPress & | |||||
- (FlowEl(ShoeFlowElNo)%StartX - Shoe%ShoeDepth) * FlowEl(ShoeFlowElNo)%dPdLfric & | |||||
- (FlowEl(ShoeFlowElNo)%StartTVD - ShoeTVD) * FlowEl(ShoeFlowElNo)%dPdLGrav)) | |||||
CALL ShoePressureDelay%Remove(PressureTimeStepDelay(3) + 1) | |||||
!FlowrateNearShoe = FlowEl(ShoeFlowElNo)%FlowRate | |||||
DO j = PressureTimeStepDelay(3) , 1 , -1 | |||||
IF (NOT(IEEE_IS_NaN(ShoePressureDelay%Array(j)))) THEN | |||||
PressureGauges(5) = INT(ShoePressureDelay%Array(j)) | |||||
EXIT | |||||
END IF | |||||
END DO | |||||
!PressureGauges(5) = INT(ShoePressureDelay%Array(PressureTimeStepDelay(3))) | |||||
DownHole%ShoePressure = real(PressureGauges(5), 8) | |||||
!IF (PressureGauges(5) >= FormationLostPressure) WRITE (*,*) 'Near Shoe Flowrate', FlowEl(ShoeFlowElNo)%FlowRate | |||||
MudSystem%ShoeMudViscosity = FlowEl(ShoeFlowElNo)%MuEff | |||||
MudSystem%ShoeMudDensity = FlowEl(ShoeFlowElNo)%Density | |||||
!WRITE (*,*) 'Drillstring speed (ft/s)' , DrillStringSpeed | |||||
!WRITE (*,*) 'shoe mud speed ', FlowEl(ShoeFlowElNo - 1)%vel | |||||
!WRITE (*,*) 'Shoe pressure (psi)', ShoePressureDelay%Array(1) | |||||
!!!!!!!!!!!!!!!!! | |||||
!!!!!!!!! 6- Pressure Before Bop | |||||
PressureGauges(6) = FlowEl(NoHorizontalEl + NoStringEl + NoAnnulusEl)%EndPress | |||||
!!!!!!!!!!!!!!!!! | |||||
101 FORMAT(4X, I2, 8X, (F8.1), 12X, (F8.3), 7X, (F8.2)) | |||||
!WRITE (*,*) ' Pump Pressure Delay', PumpPressureDelay%Array(1) | |||||
!WRITE (*,*) ' Bottom Hole Pressure Delay', BottomHolePressureDelay%Array(1) | |||||
!WRITE (*,*) ' Shoe Pressure Delay', ShoePressureDelay%Array(1) | |||||
!IF (ALLOCATED(GasPocketWeight%Array) .AND. ChokeKroneckerDelta == 1) THEN | |||||
!WRITE (*,*) 'Pocket No , Gas Pocket (psia) , Volume (gal) , Flow Induced (gpm) ' | |||||
!DO i = 1 , NoGasPocket | |||||
! WRITE (*,101) i, GasPocketNewPress%Array(i), GasPocketNewVol%Array(i) * ConvFt3toUSGal, GasPocketFlowInduced%Array(i) | |||||
!END DO | |||||
! WRITE (*,*) 'Kchoke =', Kchoke, FlowEl(OpenholeFirstEl - 1)%FlowRate | |||||
!DO i = 1 , NoGasPocket | |||||
! WRITE (*,*) 'Gas Kick Vol (gal)=' , GasPocketNewVol%Array(i) * ConvFt3toUSGal , GasPocketDeltaVol%Array(i) * ConvFt3toUSGal , GasPocketNewPress%Array(i) | |||||
!END DO | |||||
!WRITE (*,*) 'BHP (psig)=', BottomHolePress | |||||
IF (ChokeKroneckerDelta == 1) THEN | |||||
!WRITE (*,*) 'Casing Pressure' , PressureGauges(2) | |||||
!WRITE (*,*) 'Below Bit' , FlowEl(AnnulusFirstEl)%StartPress | |||||
!WRITE (*,*) 'Above Bit' , FlowEl(StringLastEl)%EndPress | |||||
!WRITE (*,*) 'Pump Pressure' , PressureGauges(1) | |||||
!WRITE (*,*) ' Kick Iteration', KickIteration | |||||
!WRITE (*,*) ' Kchoke, Q =', Kchoke, FlowEl(j)%Flowrate !, REAL((DeltaVolumePipe * ConvMinToSec / dt) + MudSystem%StringFlowRate) | |||||
!DO l = NoHorizontalEl + NoStringEl + 1 , NumbEl | |||||
! WRITE (*,*) 'El No, Fric Press Loss, density , Q', l, FlowEl(l)%FricPressLoss, FlowEl(l)%StaticPressDiff, FlowEl(l)%Density, FlowEl(l)%Flowrate | |||||
!END DO | |||||
!write(*,*) 'BackPressure=' , BackPressure | |||||
!WRITE (*,*) ' Kick Jacobian ', REAL(KickJacobian) | |||||
!WRITE (*,*) ' KickVandPFunction = ' , REAL(-KickVandPFunction) | |||||
!WRITE (*,*) ' Kick Unknown Vector = ' , REAL(KickUnknownVector) | |||||
!WRITE (*,*) 'SUM(StaticPressDiff) , SUM(FricPressLoss)', SUM(FlowEl(GasPocketElementNo(1) : i)%FricPressLoss) , SUM(FlowEl(GasPocketElementNo(1) : i)%StaticPressDiff) | |||||
!WRITE (*,*) 'Drillpipe, casing pressure', PressureGauges(1), PressureGauges(2) | |||||
END IF | |||||
!IF (NoWelltoChokeEl > 0 .AND. FlowEl(OpenholeFirstEl - 1)%MaterialType == 1 .AND. WellHeadOpen) THEN ! kick is last element in choke line and does not exit. | |||||
! KickWasExitingThroughChoke = .TRUE. | |||||
! GasPocketDensity%Array(NoGasPocket) = (GasPocketweight%Array(NoGasPocket) / GasPocketModifiedVol%Array(NoGasPocket)) / convft3toUSgal ! [lbm/ft^3 to ppg] | |||||
! ExitMass = (1.0 - (GasPocketModifiedVol%Array(NoGasPocket) / GasPocketNewVol%Array(NoGasPocket))) * GasPocketWeight%Array(NoGasPocket) ! exit mass due to expand | |||||
! WRITE (*,*) ' ExitMass due to expand = ', GasPocketModifiedVol%Array(NoGasPocket) * Convft3ToUSgal , ExitMass | |||||
!END IF | |||||
!WRITE (*,*) 'Horiz 1' | |||||
KickInFluxConditions = (Reservoir%FormationTop < TD_WellGeneral%WellTotalVerticalLength) .AND. (NOT(Reservoir%InactiveInflux)) .AND. (FormPressure > BottomHolePress + 5.0) | |||||
IF (KickInFluxConditions) THEN | |||||
KickFlux = .TRUE. | |||||
CALL NewGasKick | |||||
!WRITE (*,*) 'Kick Flux top' , KickFlux | |||||
!WRITE (*,*) 'FormPressure, BottomHolePress, FormationTop, TD_WellGeneral%WellTotalVerticalLength' , FormPressure, BottomHolePress, FormationTop, TD_WellGeneral%WellTotalVerticalLength | |||||
ELSE | |||||
IF (ALLOCATED(GasPocketWeight%Array) .AND. KickFlux) THEN | |||||
KickOffBottom = .TRUE. | |||||
WRITE (*,*) 'Kick Off Bottom' | |||||
WRITE (*,*) 'FormPressure , BottomHolePress' , FormPressure , BottomHolePress | |||||
!WRITE (*,*) 'No Press(psia) Vol(gal) Weight(lbm) Flow Induced(gpm) Flow El Press(psia)' | |||||
DO i = 1 , NoGasPocket | |||||
WRITE (*,102) i , GasPocketNewPress%Array(i), GasPocketNewVol%Array(i) * Convft3toUSgal, GasPocketWeight%Array(i), GasPocketFlowInduced%Array(i), FlowEl(GasPocketFlowEl(i , 1))%StartPress + StandardPress | |||||
END DO | |||||
END IF | |||||
KickFlux = .FALSE. | |||||
END IF | |||||
IF (ALLOCATED(KickJacobian)) OldKickJacobian = KickJacobian | |||||
102 FORMAT (I2, 3X, (F8.1), 2X, (F8.2), 2X, (F8.3), 8X, (F8.2), 10X, (F8.1)) | |||||
!!!!!!!! Auto Choke Procedure | |||||
! DO i = 1 , 5 | |||||
! AreaChange = -1.0 * (BottomHolePressure - (FormPressure + BHPSafetyMargin)) / FlowEl(OpenholeFirstEl - 1)%Flowrare**2 * 89158.0 & | |||||
! * (0.26 * 0.61)**2 * TotalOpenChokeArea**3 / (4.0 * ChokeDensity) | |||||
! CHOOKE(1)%AreaChokeFinal = CHOOKE(1)%AreaChokeFinal + AreaChange / * Convfttoinch**2 | |||||
! | |||||
! | |||||
! | |||||
! END DO | |||||
! | |||||
! | |||||
! | |||||
! | |||||
! | |||||
!WRITE (*,*) ' SecondaryKickWeight', SecondaryKickWeight | |||||
!WRITE (*,*) ' SecondaryKickVol', SecondaryKickVol | |||||
DownHole%SecondKickVolume = SecondaryKickVol | |||||
IF (WellHeadOpen == .FALSE. .OR. (FlowEl(OpenholeFirstEl - 1)%Flowrate < PressFlowrateTolerance .AND. FlowEl(AnnulusLastEl)%Flowrate < PressFlowrateTolerance)) THEN | |||||
OnShakerDensity = 0.0 | |||||
ELSE IF (FlowEl(OpenholeFirstEl - 1)%MaterialType == 1 .AND. ChokeKroneckerDelta == 1) THEN | |||||
OnShakerDensity = 2.0 | |||||
ELSE IF (ChokeKroneckerDelta == 0) THEN | |||||
OnShakerDensity = FlowEl(AnnulusLastEl)%Density | |||||
ELSE IF (ChokeKroneckerDelta == 1) THEN !!!(FlowEl(OpenholeFirstEl - 1)%Flowrate > PressFlowrateTolerance .AND. FlowEl(AnnulusLastEl)%Flowrate < PressFlowrateTolerance) THEN | |||||
OnShakerDensity = FlowEl(OpenholeFirstEl - 1)%Density | |||||
ELSE | |||||
OnShakerDensity = (FlowEl(OpenholeFirstEl - 1)%Density * FlowEl(OpenholeFirstEl - 1)%Flowrate & | |||||
+ FlowEl(AnnulusLastEl)%Density * FlowEl(AnnulusLastEl)%Flowrate) / (FlowEl(OpenholeFirstEl - 1)%Flowrate + FlowEl(AnnulusLastEl)%Flowrate) | |||||
END IF | |||||
!WRITE (*,*) 'ANINT(OnShakerDensity * 100) / 100', ANINT(OnShakerDensity * 100) / 100 , OnShakerDensity | |||||
CALL Set_MudWeightOut(ANINT(OnShakerDensity * 100) / 100) | |||||
IF (ALLOCATED(FinalFlowEl)) DEALLOCATE(FinalFlowEl) | |||||
ALLOCATE(FinalFlowEl(NumbEl)) | |||||
FinalFlowEl(:)%StartX = FlowEl(:)%StartX | |||||
FinalFlowEl(:)%EndX = FlowEl(:)%EndX | |||||
FinalFlowEl(:)%StartTVD = FlowEl(:)%StartTVD | |||||
FinalFlowEl(:)%EndTVD = FlowEl(:)%EndTVD | |||||
FinalFlowEl(:)%Length = FlowEl(:)%Length | |||||
FinalFlowEl(:)%DepthDiff = FlowEl(:)%DepthDiff | |||||
FinalFlowEl(:)%density = FlowEl(:)%density | |||||
FinalFlowEl(:)%StartPress = FlowEl(:)%StartPress | |||||
FinalFlowEl(:)%EndPress = FlowEl(:)%EndPress | |||||
FinalFlowEl(:)%dPdLFric = FlowEl(:)%dPdLFric | |||||
FinalFlowEl(:)%dPdLGrav = FlowEl(:)%dPdLGrav | |||||
!WRITE (*,*) 'FlowRate=', FlowEl(AnnulusFirstEl)%FlowRate | |||||
!WRITE (*,*) 'Pressure Loss in Drill String', SUM(FlowEl(StringFirstEl : StringLastEl)%FricPressLoss) | |||||
!WRITE (*,*) 'Pressure Loss in Annulus', SUM(FlowEl(AnnulusFirstEl : AnnulusLastEl)%FricPressLoss) | |||||
!MDObserve(:) = [3000.0 , 4349.0 , 11880.0 , 19880.0 , 21680.0] | |||||
!NomMd (:) = [3000 , 4298 , 11690 , 19690 , 21490] | |||||
!DO i = 1 , 5 | |||||
! CALL TVD_Calculator(MDObserve(i) , TVDObserve(i)) | |||||
!END DO | |||||
! | |||||
!DO i = 1 , 5 | |||||
! | |||||
! WRITE (*,*) 'MDObserve(i)', INT(NomMD(i)) | |||||
! WRITE (*,*) 'TVDObserve(i)', INT(TVDObserve(i)) | |||||
! | |||||
! DO j = StringFirstEl , StringLastEl | |||||
! IF (INT(MDObserve(i)) < INT(FinalFlowEl(j)%EndX)) EXIT | |||||
! END DO | |||||
! StPressObserve(i) = FlowEl(j)%StartPress - (MDObserve(i) - FlowEl(j)%StartX) * FlowEl(j)%dPdLfric + (TVDObserve(i) - FlowEl(j)%StartTVD) * FlowEl(j)%dPdLGrav | |||||
! WRITE (*,*) 'String Pressure', INT(StPressObserve(i)) | |||||
! | |||||
! | |||||
! | |||||
! IF (INT(MDObserve(i)) <= INT(FlowEl(AnnulusFirstEl)%StartX)) THEN !! mouse pointer is in the annulus space | |||||
! DO j = AnnulusFirstEl , AnnulusLastEl | |||||
! IF (INT(FlowEl(j)%EndX) <= INT(MDObserve(i))) EXIT | |||||
! END DO | |||||
! ELSE IF (INT(MDObserve(i)) > INT(FinalFlowEl(NumbEl)%EndX)) THEN ! mouse pointer is in the open hole space | |||||
! DO j = OpenholeFirstEl , NumbEl | |||||
! IF (INT(FinalFlowEl(j)%EndX) <= INT(MDObserve(i))) EXIT | |||||
! END DO | |||||
! END IF | |||||
! AnnPressObserve(i) = FlowEl(j)%StartPress - (FlowEl(j)%StartX - MDObserve(i)) * FlowEl(j)%dPdLfric & | |||||
! - (FlowEl(j)%StartTVD - TVDObserve(i)) * FlowEl(j)%dPdLGrav | |||||
! WRITE (*,*) 'Annulus Pressure', INT(AnnPressObserve(i)) | |||||
! | |||||
! | |||||
!END DO | |||||
END SUBROUTINE | |||||
SUBROUTINE SOLVE_LINEAR_EQUATIONS(A , x , b , error, dim) | |||||
!!! This subroutine solves a linear systems of equations Ax=b | |||||
!! if vaiable erorr changed its value to .FALSE. means that the system of equations cab not be solved | |||||
!! I use this subroutine to solve the linearized equations which uprising in calculation of volume and pressure of gas kick pockets | |||||
use KickVARIABLESModule | |||||
IMPLICIT NONE | |||||
INTEGER , INTENT(IN) :: dim | |||||
REAL(8) , DIMENSION(dim,dim) , INTENT(in) :: A | |||||
REAL , DIMENSION(dim) , INTENT(OUT) :: x | |||||
REAL(8) , DIMENSION(dim) , INTENT(in) :: b | |||||
LOGICAL , INTENT(OUT) :: error | |||||
REAL(8) , DIMENSION(:,:) , ALLOCATABLE :: m | |||||
INTEGER , DIMENSION(1) :: max_loc | |||||
REAL(8) , DIMENSION(:) , ALLOCATABLE :: temp_row | |||||
INTEGER :: n , k | |||||
!WRITE (*,*) 'SIZE(A , dim = 1), SIZE(A , dim = 2), SIZE(b)', SIZE(A , dim = 1), SIZE(A , dim = 2), SIZE(b) | |||||
error = (SIZE(A , dim = 1) /= SIZE(b)) .OR. (SIZE(A , dim = 2) /= SIZE(b)) | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 1' , error | |||||
IF (error) THEN | |||||
x = 0.0d0 | |||||
RETURN | |||||
END IF | |||||
n = SIZE(b) | |||||
ALLOCATE (m(n , n + 1) , temp_row(n + 1)) | |||||
m(1:n , 1:n) = A | |||||
m(1:n , n + 1) = b | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 2' , m | |||||
! Triangularization phase | |||||
TRIANG_LOOP: DO k = 1 , n | |||||
max_loc = MAXLOC(ABS(m(k:n , k))) | |||||
temp_row(k:n + 1) = m(k , k:n + 1) | |||||
m(k , k:n+1) = m(k-1+max_loc(1) , k:n+1) | |||||
m(k - 1 + max_loc(1) , k:n + 1) = temp_row(k:n + 1) | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 3' , max_loc | |||||
IF (m(k , k) == 0) THEN | |||||
error = .TRUE. | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 4' | |||||
EXIT TRIANG_LOOP | |||||
ELSE | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 5' | |||||
m(k , k : n + 1) = m(k , k : n + 1) / m(k , k) | |||||
m(k + 1 : n , k + 1 : n + 1) = m(k + 1 : n , k + 1 : n + 1) - SPREAD(m(k , k + 1:n + 1) , 1, n - k) * SPREAD(m(k + 1:n , k) , 2 , n - k + 1) | |||||
END IF | |||||
END DO TRIANG_LOOP | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 6' | |||||
! Back substitution phase | |||||
IF (error) THEN | |||||
x = 0.0 | |||||
ELSE | |||||
DO k = n , 1 , -1 | |||||
x(k) = REAL(m(k , n + 1) - SUM(m(k , k + 1 : n) * x(k + 1 : n))) | |||||
!WRITE (*,*) 'SOLVE_LINEAR_EQUATIONS 7' | |||||
END DO | |||||
END IF | |||||
DEALLOCATE(m , temp_row) | |||||
END SUBROUTINE solve_linear_equations | |||||
@@ -0,0 +1,32 @@ | |||||
MODULE PressureDisplayVARIABLES | |||||
USE DynamicRealArray | |||||
IMPLICIT NONE | |||||
INTEGER :: NoGauges | |||||
REAL , DIMENSION(6) :: PressureGauges | |||||
INTEGER :: SoundSpeed ! speed of sound [ft/s] | |||||
INTEGER , DIMENSION(3) :: PressureTimeStepDelay | |||||
TYPE(DynamicRealArrayType) :: PumpPressureDelay | |||||
TYPE(DynamicRealArrayType) :: CasingPressureDelay | |||||
TYPE(DynamicRealArrayType) :: BottomHolePressureDelay | |||||
TYPE(DynamicRealArrayType) :: ShoePressureDelay | |||||
TYPE :: ObservationAndGaugePointsInformations ! We have some gauges and may be have many observation points like casing shoe, bottomhole , etc. | |||||
! This module stores information of these points to calculate pressure, density and other desired properties | |||||
! at these points | |||||
! Locations: 1: Stand Pipe , 2: Choke Manifold, 3: Botton Hole, 4: Under Bit, 5: Shoe, 6: Before BOP | |||||
INTEGER :: ElementNo ! Element Nubmer based on mud elements | |||||
REAL :: DistancetoRefrence ! Distance from pump or the end of fluid path [ft] | |||||
REAL :: ElementTrueDepth ! True depth of point or gauge [ft] | |||||
REAL :: Pressure ! Pressure [psi] | |||||
END TYPE | |||||
!TYPE(ObservationAndGaugePointsInformations) , ALLOCATABLE :: GaugePoint(:) | |||||
TYPE(ObservationAndGaugePointsInformations) , ALLOCATABLE :: ObservationPoint(:) | |||||
END MODULE |
@@ -0,0 +1,178 @@ | |||||
MODULE FricPressDropVars | |||||
!! Record of revisions | |||||
!! Date Programmer Discription of change | |||||
!! ------ ------------ ----------------------- | |||||
!! 1396/07/26 Sheikh Original code | |||||
!! | |||||
IMPLICIT NONE | |||||
REAL :: TotFricPressLoss ! Total Frictional Pressure Loss [psi] | |||||
REAL :: FlowrateNearShoe | |||||
INTEGER :: NoHorizontalEl ! number of elements in horizontal pump to string line | |||||
INTEGER :: NoStringEl ! number of elements in string | |||||
INTEGER :: NoAnnulusEl ! number of elements in annulus space | |||||
INTEGER :: NoWellToChokeEl ! number of elements in well head to choke manifold | |||||
INTEGER :: NoOpenHoleEl ! number of elements in openhole | |||||
INTEGER :: NumbEl ! number of flow elements in horizontal line, string, annulus and openhole | |||||
INTEGER :: StringFirstEl ! number of first string element | |||||
INTEGER :: StringLastEl ! number of last string element | |||||
INTEGER :: AnnulusFirstEl ! number of first annulus element | |||||
INTEGER :: AnnulusLastEl ! number of last annulus element | |||||
INTEGER :: ChokeFirstEl ! number of first choke element | |||||
INTEGER :: ChokeLastEl ! number of last choke element | |||||
INTEGER :: OpenholeFirstEl ! number of first openhole element | |||||
INTEGER :: ShoeFlowElNo ! the flow element that starts from shoe, in other word the number of upper element adjacent to shoe | |||||
REAL :: KBOP ! DeltaPBOP = KBOP * Q**2 [psi * min^2 / gal^2] | |||||
REAL :: KBit ! DeltaPBit = KBit * Q**2 [psi * min^2 / gal^2] | |||||
!!!! Choke Variables | |||||
REAL :: BackPressure , NewBackPressure ! back pressure at riser or choke line [psi] | |||||
REAL :: Kchoke ! DeltaPchoke = Kchoke * Q**2 [psi * min^2 / gal^2] | |||||
REAL :: TotalOpenChokeArea , OldTotalOpenChokeArea , ChokeBypassArea , NewTotalOpenChokeArea , AreaChange | |||||
REAL :: BHPSafetyMargin , AChBHPTol ! BHP safety margin and BHP Tolerance in Auto Choke mode [psi] | |||||
REAL(8) :: OnShakerDensity ! Outlet Density of well for displaying in drillwatch and data [ppg] | |||||
LOGICAL :: FloatValveIn | |||||
LOGICAL :: FloatValveOpen , FloatValveWasOpen | |||||
LOGICAL :: BitTotallyPluged | |||||
REAL :: ClingingFactor = 0.45 ! in calculating surge and swab pressure changes | |||||
REAL :: MudCompressibility = 2.7E-6 ! Volumne change relative to Volume/1psi, for example for change of 1000 psi in pressure, volume changes 0.27% [1/psi] | |||||
REAL :: FloatValveMinOpenPressure = 1.0 ! minimum pressure that opens the float valve [psi] | |||||
REAL :: StMudVol ! Total mud volume of Horizontal and String that may be compressed [gal] | |||||
REAL :: AnnMudVol ! Total mud volume of Bottom hole, Annulus and Choke line that may be compressed [gal] | |||||
REAL :: PumpToManifoldMudVol | |||||
REAL :: StCompressedMudVol ! Compressed mud volume in Horizontal and String [gal] | |||||
REAL :: AnnCompressedMudVol ! Compressed mud volume in Bottom hole, Annulus and Choke line [gal] | |||||
REAL :: PumpToManifoldCompressedMudVol | |||||
REAL :: StDeltaPDueToCompressibility ! Pressure increase due to mud compressibility in Horizontal and String [psi] | |||||
REAL :: AnnDeltaPDueToCompressibility ! Pressure increase due to mud compressibility in Bottom hole, Annulus and Choke line [psi] (usually when wellhead is closed) | |||||
REAL :: PumpToManifoldDeltaPDueToCompressibility | |||||
REAL :: StDeltaPtoDeltaVCompressibility ! string pressure change due to compressibility [psi/gal] | |||||
REAL :: AnnDeltaPtoDeltaVCompressibility ! annulus and openhole pressure change due to compressibility [psi/gal] | |||||
!!!! Problem Variables (Choke and Bit) | |||||
INTEGER :: ManChoke1Plug , ManChoke2Plug ! = 1 if choke is plugged , = 0 else | |||||
INTEGER :: ManChoke1Washout , ManChoke2Washout ! = 1 if choke is washed out , = 0 else | |||||
INTEGER :: BitJetsPlugged , BitJetsWashedOut | |||||
INTEGER :: CasingPressure_DataDisplayMalF, CasingPressure_ChokeMalF | |||||
!!!!!! Note that bit is not an element in these calculations | |||||
TYPE, PUBLIC :: PressDropCalcElemInfo | |||||
!! Geometrical variables | |||||
REAL(8) :: Length ! Length of a Flow element [ft] | |||||
REAL(8) :: DepthDiff ! Difference between depth of start and end of element [ft] | |||||
REAL(8) :: StartX , EndX ! start and end point (measured depth) of flow element [ft] | |||||
REAL(8) :: StartTVD , EndTVD ! Start and End point True Vertical Depth of flow element [ft] | |||||
REAL :: Od , Id , Dhyd ! Outer, Inner and hydraulic diameter of flow element [in] | |||||
REAL :: Area ! area of element [ft^2] | |||||
INTEGER :: alpha ! geometry factor: 0 = pipe (ID=0) , 1 = annulus | |||||
INTEGER :: FrictionDirection ! = 1 if flowrate is positive, so frictional pressure gradient is in direction of preassumed | |||||
! flowrate, = -1 if not above condition usually in Swab conditions | |||||
!! Flow variables | |||||
INTEGER :: MaterialType ! = 0 for mud , = 2 for gas | |||||
REAL :: volume , vel , density , FlowRate ! volume [ft^3], velocity [ft/s], density of fluid flow [ppg], flow rate [gpm] | |||||
REAL :: Gf ! geometry shear rate correction [-] | |||||
!! Rheological and frictional variables | |||||
REAL :: Theta600 , Theta300 ! Fann data at 600 and 300 rpm as rheological data | |||||
! REAL(8) :: VelCritBing , VelCritPow ! critical velocity in Bingham Plastic and Power law model [ft/min] | |||||
REAL :: muPlastic , YieldP ! plastic viscosity [cp] and yield point [lbf/(100*ft^2)] | |||||
REAL :: mueff ! Effective or apparent viscosity which is used in calculation of generalized Reynolds number | |||||
REAL :: nIndex , kIndex ! n: flow behaivior index [-] and k: consistency factor [lbf*s^n/(100*ft^2)] | |||||
REAL :: gammaW , tauW ! shear rate at the wall [1/s] and wall shear stress [lbf/(100*ft^2)] | |||||
REAL :: GenRe ! generalized Reynolds number in power law model [-] | |||||
REAL :: ReCrit = 2100.0 ! Critical Reynolds number for Newtonian model and Bingham plastic model | |||||
REAL :: ReCritLam , ReCritTurb ! laminar and turbulent critical Reynolds | |||||
REAL :: f ! Fanning friction factor [-] | |||||
REAL :: a , b ! parameters for calculationg friction factor in turbulent regime for power law model [-] | |||||
LOGICAL :: LaminarRegime ! = .TRUE. if flow regime is laminar and = .FALSE. if flowregime is not | |||||
LOGICAL :: TurbulentRegime ! = .TRUE. if flow regime is turbulent and = .FALSE. if flowregime is not | |||||
!! Pressure change variables | |||||
REAL :: StartPress , EndPress ! Pressure at start and end of an element [psi] | |||||
REAL :: dPdLFric ! frictional pressure drop gradient in each element [psi/ft] | |||||
REAL :: dPdLGrav ! gravitional pressure gradient = 0.052 * Density [psi/ft] | |||||
REAL :: FricPressLoss ! frictional pressure loss in each element [psi] | |||||
REAL :: StaticPressDiff ! static pressure difference between top and bottom of a pocket [psi] always positive | |||||
REAL :: FricToQPartialDiff ! partial differentiation of friction relative to volume flow rate | |||||
END TYPE PressDropCalcElemInfo | |||||
TYPE (PressDropCalcElemInfo) , ALLOCATABLE :: FlowEl(:) ! FlowEl: Pressure Drop Calculation Elements The dimension is equal to the number of flow elements | |||||
TYPE, PUBLIC :: FinalPressDropCalcElemInfo | |||||
!!! for use in calculationg properties of a point in 'downhole view' page | |||||
REAL(8) :: StartX , EndX , StartTVD , EndTVD , Length , DepthDiff ! start and end point of flow element [ft] | |||||
REAL :: density ! density of fluid flow [ppg], flow rate [gpm] | |||||
REAL :: StartPress ! Pressure at start of an element [psi] | |||||
REAL :: EndPress ! Pressure at end of an element [psi] | |||||
REAL :: dPdLFric ! frictional pressure drop gradient in each element [psi/ft] | |||||
REAL :: dPdLGrav ! gravitional pressure gradient = 0.052 * Density [psi/ft] | |||||
END TYPE FinalPressDropCalcElemInfo | |||||
TYPE (FinalPressDropCalcElemInfo) , ALLOCATABLE :: FinalFlowEl(:) ! FlowEl: Pressure Drop Calculation Elements The dimension is equal to the number of flow elements | |||||
END MODULE FricPressDropVars | |||||
MODULE UTUBEVARS | |||||
REAL :: QUTubeInput ! flow rate from string to annulus which caused by head difference at two sides of U-tube [gpm] | |||||
REAL :: QUtubeOutput ! flow rate from annulus to string which caused by head difference at two sides of U-tube [gpm] | |||||
REAL :: PressureDp ! pressure at bit or end of drill string from drill string path [psi] | |||||
REAL :: PressureAnn ! pressure at bit or end of drill string from annular path [psi] | |||||
END MODULE | |||||
SUBROUTINE DeallocateFlowTypes | |||||
USE FricPressDropVarsModule | |||||
use PressureDisplayVARIABLESModule | |||||
use KickVARIABLESModule | |||||
IMPLICIT NONE | |||||
IF (ALLOCATED(FlowEl)) DEALLOCATE(FlowEl) | |||||
IF (ALLOCATED(FinalFlowEl)) DEALLOCATE(FinalFlowEl) | |||||
IF (ALLOCATED(GasPocketWeight%Array)) CALL GasPocketWeight%Empty() | |||||
IF (ALLOCATED(GasPocketNewPress%Array)) CALL GasPocketNewPress%Empty() | |||||
IF (ALLOCATED(GasPocketOldPress%Array)) CALL GasPocketOldPress%Empty() | |||||
IF (ALLOCATED(GasPocketNewTemp%Array)) CALL GasPocketNewTemp%Empty() | |||||
IF (ALLOCATED(GasPocketOldTemp%Array)) CALL GasPocketOldTemp%Empty() | |||||
IF (ALLOCATED(GasPocketNewVol%Array)) CALL GasPocketNewVol%Empty() | |||||
IF (ALLOCATED(GasPocketOldVol%Array)) CALL GasPocketOldVol%Empty() | |||||
IF (ALLOCATED(GasPocketdeltaVol%Array)) CALL GasPocketdeltaVol%Empty() | |||||
IF (ALLOCATED(GasPocketModifiedVol%Array)) CALL GasPocketModifiedVol%Empty() | |||||
IF (ALLOCATED(GasPocketFlowInduced%Array)) CALL GasPocketFlowInduced%Empty() | |||||
IF (ALLOCATED(GasPocketDensity%Array)) CALL GasPocketDensity%Empty() | |||||
IF (ALLOCATED(GasPocketCompressibility%Array)) CALL GasPocketCompressibility%Empty() | |||||
IF (ALLOCATED(GasPocketFlowEl)) DEALLOCATE(GasPocketFlowEl) | |||||
IF (ALLOCATED(KickJacobian)) DEALLOCATE(KickJacobian) | |||||
IF (ALLOCATED(OldKickJacobian)) DEALLOCATE(OldKickJacobian) | |||||
IF (ALLOCATED(KickVandPFunction)) DEALLOCATE(KickVandPFunction) | |||||
IF (ALLOCATED(KickUnknownVector)) DEALLOCATE(KickUnknownVector) | |||||
IF (ALLOCATED(KickCorrectionVector)) DEALLOCATE(KickCorrectionVector) | |||||
END SUBROUTINE | |||||