@@ -8,11 +8,11 @@ module CCommon | |||
subroutine SetStandRack(v) | |||
implicit none | |||
integer, intent(in) :: v | |||
if(StandRack == v) return | |||
StandRack = v | |||
call OnStandRackChange%Run(v) | |||
if(Common%StandRack == v) return | |||
Common%StandRack = v | |||
call Common%OnStandRackChange%Run(v) | |||
#ifdef deb | |||
print*, 'StandRack=', StandRack | |||
print*, 'StandRack=', Common%StandRack | |||
#endif | |||
end subroutine | |||
@@ -32,19 +32,19 @@ module CCommon | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDrillWatchOperationMode | |||
!DEC$ ATTRIBUTES ALIAS: 'GetDrillWatchOperationMode' :: GetDrillWatchOperationMode | |||
implicit none | |||
GetDrillWatchOperationMode = DrillWatchOperationMode | |||
GetDrillWatchOperationMode = Common%DrillWatchOperationMode | |||
end function | |||
integer function GetStandRack() | |||
implicit none | |||
GetStandRack = StandRack | |||
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 = StandRack | |||
GetStandRack_WN = Common%StandRack | |||
end function | |||
@@ -3,10 +3,13 @@ module CCommonVariables | |||
implicit none | |||
public | |||
! Input vars | |||
integer :: StandRack | |||
type(IntegerEventHandler) :: OnStandRackChange | |||
! Output vars | |||
logical :: DrillWatchOperationMode | |||
contains | |||
type :: CommonType | |||
! Input vars | |||
integer :: StandRack | |||
type(IntegerEventHandler) :: OnStandRackChange | |||
! Output vars | |||
logical :: DrillWatchOperationMode | |||
end type | |||
type(CommonType):: Common | |||
contains | |||
end module CCommonVariables |
@@ -9,7 +9,7 @@ module CLesson | |||
implicit none | |||
logical, intent(in) :: path | |||
logical, intent(in) :: survey | |||
IsPathGeneration = path | |||
IsWellSurveyData = survey | |||
Lesson%IsPathGeneration = path | |||
Lesson%IsWellSurveyData = survey | |||
end subroutine | |||
end module CLesson |
@@ -1,9 +1,9 @@ | |||
module CLessonVariables | |||
implicit none | |||
public | |||
type:: LessonType | |||
logical :: IsPathGeneration | |||
logical :: IsWellSurveyData | |||
contains | |||
end type LessonType | |||
type(LessonType)::Lesson | |||
end module CLessonVariables |
@@ -17,14 +17,14 @@ module CDownHole | |||
!DEC$ ATTRIBUTES DLLEXPORT::AnnalusDrillMud | |||
!DEC$ ATTRIBUTES ALIAS: 'AnnalusDrillMud' :: AnnalusDrillMud | |||
implicit none | |||
AnnDrillMud = .true. | |||
DownHole%AnnDrillMud = .true. | |||
end subroutine AnnalusDrillMud | |||
subroutine AnnalusCirculateMud | |||
!DEC$ ATTRIBUTES DLLEXPORT::AnnalusCirculateMud | |||
!DEC$ ATTRIBUTES ALIAS: 'AnnalusCirculateMud' :: AnnalusCirculateMud | |||
implicit none | |||
AnnCirculateMud = .true. | |||
DownHole%AnnCirculateMud = .true. | |||
end subroutine AnnalusCirculateMud | |||
@@ -39,7 +39,7 @@ module CDownHole | |||
!DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidsCount | |||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidsCount' :: GetAnnalusFluidsCount | |||
implicit none | |||
GetAnnalusFluidsCount = size(AnnalusFluids) | |||
GetAnnalusFluidsCount = size(DownHole%AnnalusFluids) | |||
!GetAnnalusFluidsCount = AnnalusFluidsCount | |||
end function GetAnnalusFluidsCount | |||
@@ -51,13 +51,13 @@ module CDownHole | |||
integer, intent(in) :: count | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
if(.not.allocated(AnnalusFluids)) return | |||
if(.not.allocated(DownHole%AnnalusFluids)) return | |||
do i = 1, count | |||
item => array(i) | |||
item%StartMd = AnnalusFluids(i)%StartMd | |||
item%EndMd = AnnalusFluids(i)%EndMd | |||
item%Density = AnnalusFluids(i)%Density | |||
item%MudType = AnnalusFluids(i)%MudType | |||
item%StartMd = DownHole%AnnalusFluids(i)%StartMd | |||
item%EndMd = DownHole%AnnalusFluids(i)%EndMd | |||
item%Density = DownHole%AnnalusFluids(i)%Density | |||
item%MudType = DownHole%AnnalusFluids(i)%MudType | |||
end do | |||
end subroutine GetAnnalusFluids | |||
@@ -67,7 +67,7 @@ module CDownHole | |||
!DEC$ ATTRIBUTES ALIAS: 'GetStringFluidsCount' :: GetStringFluidsCount | |||
implicit none | |||
!GetStringFluidsCount = StringFluidsCount | |||
GetStringFluidsCount = size(StringFluids) | |||
GetStringFluidsCount = size(DownHole%StringFluids) | |||
end function GetStringFluidsCount | |||
subroutine GetStringFluids(count, array) | |||
@@ -78,13 +78,13 @@ module CDownHole | |||
integer, intent(in) :: count | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
if(.not.allocated(StringFluids)) return | |||
if(.not.allocated(DownHole%StringFluids)) return | |||
do i = 1, count | |||
item => array(i) | |||
item%StartMd = StringFluids(i)%StartMd | |||
item%EndMd = StringFluids(i)%EndMd | |||
item%Density = StringFluids(i)%Density | |||
item%MudType = StringFluids(i)%MudType | |||
item%StartMd = DownHole%StringFluids(i)%StartMd | |||
item%EndMd = DownHole%StringFluids(i)%EndMd | |||
item%Density = DownHole%StringFluids(i)%Density | |||
item%MudType = DownHole%StringFluids(i)%MudType | |||
end do | |||
end subroutine GetStringFluids | |||
@@ -93,7 +93,7 @@ module CDownHole | |||
!DEC$ ATTRIBUTES DLLEXPORT::GetStringCount | |||
!DEC$ ATTRIBUTES ALIAS: 'GetStringCount' :: GetStringCount | |||
implicit none | |||
GetStringCount = StringCount | |||
GetStringCount = DownHole%StringCount | |||
!GetStringCount = 4 | |||
end function GetStringCount | |||
@@ -126,22 +126,22 @@ module CDownHole | |||
implicit none | |||
!BopElement | |||
if(associated(BopElementsPtr)) call BopElementsPtr(BopElements) | |||
if(associated(BopElementsPtr)) call BopElementsPtr(DownHole%BopElements) | |||
!Annalus | |||
if(associated(AnnalusMudCountPtr)) call AnnalusMudCountPtr(AnnalusFluidsCount) | |||
if(associated(AnnalusMudArrayPtr)) call AnnalusMudArrayPtr(AnnalusFluids) | |||
if(associated(AnnalusMudCountPtr)) call AnnalusMudCountPtr(DownHole%AnnalusFluidsCount) | |||
if(associated(AnnalusMudArrayPtr)) call AnnalusMudArrayPtr(DownHole%AnnalusFluids) | |||
!string | |||
if(associated(StringMudCountPtr)) call StringMudCountPtr(StringFluidsCount) | |||
if(associated(StringMudArrayPtr)) call StringMudArrayPtr(StringFluids) | |||
if(associated(StringMudCountPtr)) call StringMudCountPtr(DownHole%StringFluidsCount) | |||
if(associated(StringMudArrayPtr)) call StringMudArrayPtr(DownHole%StringFluids) | |||
!components | |||
if(associated(StringComponentCountPtr)) call StringComponentCountPtr(StringCount) | |||
if(associated(StringComponentArrayPtr)) call StringComponentArrayPtr(String) | |||
if(associated(StringComponentCountPtr)) call StringComponentCountPtr(DownHole%StringCount) | |||
if(associated(StringComponentArrayPtr)) call StringComponentArrayPtr(DownHole%String) | |||
end subroutine GetDownhole | |||
@@ -164,7 +164,7 @@ module CDownHole | |||
!DEC$ ATTRIBUTES ALIAS: 'GetDrillPipePressureH' :: GetDrillPipePressureH | |||
use PressureDisplayVARIABLES | |||
implicit none | |||
GetDrillPipePressureH = DrillPipePressure !real(PressureGauges(1), 8) ! | |||
GetDrillPipePressureH = DownHole%DrillPipePressure !real(PressureGauges(1), 8) ! | |||
end function | |||
real(8) function GetCasingPressureH() | |||
@@ -177,7 +177,7 @@ module CDownHole | |||
! CasingPressure = real(int(FinalFlowEl(AnnulusLastEl)%EndPress), 8) !CasingPressure | |||
! endif | |||
!endif | |||
GetCasingPressureH = CasingPressure | |||
GetCasingPressureH = DownHole%CasingPressure | |||
end function | |||
real(8) function GetShoePressure() | |||
@@ -185,7 +185,7 @@ module CDownHole | |||
!DEC$ ATTRIBUTES ALIAS: 'GetShoePressure' :: GetShoePressure | |||
use PressureDisplayVARIABLES | |||
implicit none | |||
GetShoePressure = ShoePressure !real(PressureGauges(5), 8) ! | |||
GetShoePressure = DownHole%ShoePressure !real(PressureGauges(5), 8) ! | |||
end function | |||
real(8) function GetBottomHolePressure() | |||
@@ -193,21 +193,21 @@ module CDownHole | |||
!DEC$ ATTRIBUTES ALIAS: 'GetBottomHolePressure' :: GetBottomHolePressure | |||
use PressureDisplayVARIABLES | |||
implicit none | |||
GetBottomHolePressure = BottomHolePressure !real(PressureGauges(3), 8) ! | |||
GetBottomHolePressure = DownHole%BottomHolePressure !real(PressureGauges(3), 8) ! | |||
end function | |||
real(8) function GetFormationPressure() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetFormationPressure | |||
!DEC$ ATTRIBUTES ALIAS: 'GetFormationPressure' :: GetFormationPressure | |||
implicit none | |||
GetFormationPressure = FormationPressure | |||
GetFormationPressure = DownHole%FormationPressure | |||
end function | |||
real function GetInfluxRate() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetInfluxRate | |||
!DEC$ ATTRIBUTES ALIAS: 'GetInfluxRate' :: GetInfluxRate | |||
implicit none | |||
GetInfluxRate = InfluxRate | |||
GetInfluxRate = DownHole%InfluxRate | |||
end function | |||
real function GetKickVolume() | |||
@@ -217,7 +217,7 @@ module CDownHole | |||
!KickVolume = KickVolume + 1 | |||
GetKickVolume = KickVolume | |||
GetKickVolume = DownHole%KickVolume | |||
end function | |||
real function GetSecondKickVolume() | |||
@@ -227,14 +227,14 @@ module CDownHole | |||
!SecondKickVolume = SecondKickVolume + 1 | |||
GetSecondKickVolume = SecondKickVolume | |||
GetSecondKickVolume = DownHole%SecondKickVolume | |||
end function | |||
real function GetPermeabilityExposedHeight() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPermeabilityExposedHeight | |||
!DEC$ ATTRIBUTES ALIAS: 'GetPermeabilityExposedHeight' :: GetPermeabilityExposedHeight | |||
implicit none | |||
GetPermeabilityExposedHeight = PermeabilityExposedHeight | |||
GetPermeabilityExposedHeight = DownHole%PermeabilityExposedHeight | |||
end function | |||
@@ -243,21 +243,21 @@ module CDownHole | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDensityH | |||
!DEC$ ATTRIBUTES ALIAS: 'GetDensityH' :: GetDensityH | |||
implicit none | |||
GetDensityH = Density | |||
GetDensityH = DownHole%Density | |||
end function | |||
real(8) function GetPressureH() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPressureH | |||
!DEC$ ATTRIBUTES ALIAS: 'GetPressureH' :: GetPressureH | |||
implicit none | |||
GetPressureH = Pressure | |||
GetPressureH = DownHole%Pressure | |||
end function | |||
real(8) function GetTemperatureH() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTemperatureH | |||
!DEC$ ATTRIBUTES ALIAS: 'GetTemperatureH' :: GetTemperatureH | |||
implicit none | |||
GetTemperatureH = Temperature | |||
GetTemperatureH = DownHole%Temperature | |||
end function | |||
@@ -265,14 +265,14 @@ module CDownHole | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHeightH | |||
!DEC$ ATTRIBUTES ALIAS: 'GetHeightH' :: GetHeightH | |||
implicit none | |||
GetHeightH = Height | |||
GetHeightH = DownHole%Height | |||
end function | |||
real(8) function GetVolumeH() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: GetVolumeH | |||
!DEC$ ATTRIBUTES ALIAS: 'GetVolumeH' :: GetVolumeH | |||
implicit none | |||
GetVolumeH = Volume | |||
GetVolumeH = DownHole%Volume | |||
end function | |||
end module CDownHole |
@@ -5,36 +5,37 @@ module CDownHoleVariables | |||
use CLog4 | |||
implicit none | |||
public | |||
type :: DownHoleType | |||
logical :: AnnDrillMud | |||
logical :: AnnCirculateMud | |||
logical :: AnnDrillMud | |||
logical :: AnnCirculateMud | |||
integer :: AnnalusFluidsCount = 0 | |||
integer :: StringFluidsCount = 0 | |||
type(CFluid), allocatable, target :: AnnalusFluids(:) | |||
type(CFluid), allocatable :: StringFluids(:) | |||
integer :: StringCount = 0 | |||
type(CStringComponent), allocatable :: String(:) | |||
type(CBopElement), allocatable :: BopElements(:) | |||
real(8) :: DrillPipePressure | |||
real(8) :: CasingPressure | |||
real(8) :: ShoePressure | |||
real(8) :: BottomHolePressure | |||
real(8) :: FormationPressure | |||
real :: InfluxRate | |||
real :: KickVolume | |||
real :: SecondKickVolume | |||
real :: PermeabilityExposedHeight | |||
real(8) :: Density | |||
real(8) :: Pressure | |||
real(8) :: Temperature | |||
real(8) :: Height | |||
real(8) :: Volume | |||
integer :: AnnalusFluidsCount = 0 | |||
integer :: StringFluidsCount = 0 | |||
type(CFluid), allocatable :: AnnalusFluids(:) !, target | |||
type(CFluid), allocatable :: StringFluids(:) | |||
integer :: StringCount = 0 | |||
type(CStringComponent), allocatable :: String(:) | |||
type(CBopElement), allocatable :: BopElements(:) | |||
real(8) :: DrillPipePressure | |||
real(8) :: CasingPressure | |||
real(8) :: ShoePressure | |||
real(8) :: BottomHolePressure | |||
real(8) :: FormationPressure | |||
real :: InfluxRate | |||
real :: KickVolume | |||
real :: SecondKickVolume | |||
real :: PermeabilityExposedHeight | |||
real(8) :: Density | |||
real(8) :: Pressure | |||
real(8) :: Temperature | |||
real(8) :: Height | |||
real(8) :: Volume | |||
end type DownHoleType | |||
type(DownHoleType):: DownHole | |||
contains | |||
subroutine SetAnnalusFluids(count, array) | |||
@@ -43,40 +44,40 @@ module CDownHoleVariables | |||
integer :: i, offset | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
AnnalusFluidsCount = count | |||
DownHole%AnnalusFluidsCount = count | |||
print*, 'AnnalusFluidsCount = ', count | |||
if(size(AnnalusFluids) > 0) then | |||
deallocate(AnnalusFluids) | |||
if(size(DownHole%AnnalusFluids) > 0) then | |||
deallocate(DownHole%AnnalusFluids) | |||
end if | |||
if(count > 0) then | |||
offset = 0; | |||
item => array(1) | |||
if(item%StartMd > 0) then | |||
AnnalusFluidsCount = AnnalusFluidsCount + 1 | |||
DownHole%AnnalusFluidsCount = DownHole%AnnalusFluidsCount + 1 | |||
offset = 1; | |||
allocate(AnnalusFluids(AnnalusFluidsCount)) | |||
AnnalusFluids(1)%StartMd = 0 | |||
AnnalusFluids(1)%EndMd = item%StartMd | |||
AnnalusFluids(1)%Density = 0 | |||
AnnalusFluids(1)%MudType = FLUID_NO_MUD | |||
allocate(DownHole%AnnalusFluids(DownHole%AnnalusFluidsCount)) | |||
DownHole%AnnalusFluids(1)%StartMd = 0 | |||
DownHole%AnnalusFluids(1)%EndMd = item%StartMd | |||
DownHole%AnnalusFluids(1)%Density = 0 | |||
DownHole%AnnalusFluids(1)%MudType = FLUID_NO_MUD | |||
endif | |||
!if(associated(AnnalusMudCountPtr)) then | |||
! call AnnalusMudCountPtr(AnnalusFluidsCount) | |||
!end if | |||
if(.not.allocated(AnnalusFluids))allocate(AnnalusFluids(AnnalusFluidsCount)) | |||
if(.not.allocated(DownHole%AnnalusFluids))allocate(DownHole%AnnalusFluids(DownHole%AnnalusFluidsCount)) | |||
!print*, '============START-AN============' | |||
if(item%StartMd < 0) AnnalusFluids(1)%StartMd = 0 | |||
if(item%StartMd < 0) DownHole%AnnalusFluids(1)%StartMd = 0 | |||
do i = 1, count | |||
item => array(i) | |||
AnnalusFluids(i + offset)%StartMd = item%StartMd | |||
if(i==1) AnnalusFluids(i)%StartMd = 0 | |||
DownHole%AnnalusFluids(i + offset)%StartMd = item%StartMd | |||
if(i==1) DownHole%AnnalusFluids(i)%StartMd = 0 | |||
!print*, 'AnnalusFluids(',i,')%StartMd=', AnnalusFluids(i)%StartMd | |||
AnnalusFluids(i + offset)%EndMd = item%EndMd | |||
DownHole%AnnalusFluids(i + offset)%EndMd = item%EndMd | |||
!print*, 'AnnalusFluids(',i,')%EndMd=', AnnalusFluids(i)%EndMd | |||
AnnalusFluids(i + offset)%Density = item%Density | |||
DownHole%AnnalusFluids(i + offset)%Density = item%Density | |||
!print*, 'AnnalusFluids(',i,')%Density=', AnnalusFluids(i)%Density | |||
AnnalusFluids(i + offset)%MudType = item%MudType | |||
DownHole%AnnalusFluids(i + offset)%MudType = item%MudType | |||
!print*, 'AnnalusFluids(',i,')%MudType=', AnnalusFluids(i)%MudType | |||
!print*, '----------------------------' | |||
end do | |||
@@ -94,10 +95,10 @@ module CDownHoleVariables | |||
integer :: i, offset !, startArr | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
StringFluidsCount = count | |||
DownHole%StringFluidsCount = count | |||
print*, 'StringFluidsCount = ', count | |||
if(size(StringFluids) > 0) then | |||
deallocate(StringFluids) | |||
if(size(DownHole%StringFluids) > 0) then | |||
deallocate(DownHole%StringFluids) | |||
end if | |||
!startArr = 1 | |||
@@ -116,30 +117,30 @@ module CDownHoleVariables | |||
!if(count <= 0) return | |||
if(item%StartMd > 0) then | |||
StringFluidsCount = StringFluidsCount + 1 | |||
DownHole%StringFluidsCount = DownHole%StringFluidsCount + 1 | |||
offset = offset + 1 | |||
allocate(StringFluids(StringFluidsCount)) | |||
StringFluids(1)%StartMd = 0 | |||
StringFluids(1)%EndMd = item%StartMd | |||
StringFluids(1)%Density = 0 | |||
StringFluids(1)%MudType = FLUID_NO_MUD | |||
allocate(DownHole%StringFluids(DownHole%StringFluidsCount)) | |||
DownHole%StringFluids(1)%StartMd = 0 | |||
DownHole%StringFluids(1)%EndMd = item%StartMd | |||
DownHole%StringFluids(1)%Density = 0 | |||
DownHole%StringFluids(1)%MudType = FLUID_NO_MUD | |||
endif | |||
!if(associated(StringMudCountPtr)) then | |||
! call StringMudCountPtr(count) | |||
!end if | |||
if(.not.allocated(StringFluids))allocate(StringFluids(StringFluidsCount)) | |||
if(.not.allocated(DownHole%StringFluids))allocate(DownHole%StringFluids(DownHole%StringFluidsCount)) | |||
!print*, '============START-ST============' | |||
!print*, 'count=', count | |||
do i = 1, count | |||
item => array(i) | |||
StringFluids(i + offset)%StartMd = item%StartMd | |||
if(i==1) StringFluids(i)%StartMd = 0 | |||
DownHole%StringFluids(i + offset)%StartMd = item%StartMd | |||
if(i==1) DownHole%StringFluids(i)%StartMd = 0 | |||
!print*, 'StringFluids(i)%StartMd=', StringFluids(i)%StartMd | |||
StringFluids(i + offset)%EndMd = item%EndMd | |||
DownHole%StringFluids(i + offset)%EndMd = item%EndMd | |||
!print*, 'StringFluids(i)%EndMd=', StringFluids(i)%EndMd | |||
StringFluids(i + offset)%Density = item%Density | |||
StringFluids(i + offset)%MudType = item%MudType | |||
DownHole%StringFluids(i + offset)%Density = item%Density | |||
DownHole%StringFluids(i + offset)%MudType = item%MudType | |||
!print*, '----------------------------' | |||
end do | |||
!!if(item%StartMd < 0) StringFluids(1)%StartMd = 0 | |||
@@ -157,15 +158,15 @@ module CDownHoleVariables | |||
integer :: i !, j | |||
type(CStringComponents), intent(inout), target :: array(count) | |||
type(CStringComponents), pointer :: item | |||
StringCount = count | |||
if(size(String) > 0) then | |||
deallocate(String) | |||
DownHole%StringCount = count | |||
if(size(DownHole%String) > 0) then | |||
deallocate(DownHole%String) | |||
end if | |||
if(count > 0) then | |||
!if(associated(StringComponentCountPtr)) then | |||
! call StringComponentCountPtr(count) | |||
!end if | |||
allocate(String(count)) | |||
allocate(DownHole%String(count)) | |||
!j = 0 | |||
!print*, '============CMP-ST============' | |||
!call Log_3( '============CMP-ST============') | |||
@@ -177,20 +178,20 @@ module CDownHoleVariables | |||
!String(i)%DownDepth = item%DownDepth | |||
!String(i)%Od = item%Od | |||
!String(i)%Id = item%Id | |||
String(i)%ComponentType= item%ComponentType | |||
DownHole%String(i)%ComponentType= item%ComponentType | |||
!j = j + 1 | |||
String(i)%StartMd = item%TopDepth | |||
String(i)%EndMd = item%DownDepth | |||
DownHole%String(i)%StartMd = item%TopDepth | |||
DownHole%String(i)%EndMd = item%DownDepth | |||
String(i)%ComponentType=0 | |||
DownHole%String(i)%ComponentType=0 | |||
!if(item%ComponentType > 4 ) then | |||
! String(i)%ComponentType=0 | |||
! String(i)%StartMd = 0 | |||
!endif | |||
if(item%ComponentType == 3) String(i)%ComponentType=0 | |||
if(item%ComponentType == 4) String(i)%ComponentType=1 | |||
if(item%ComponentType == 2) String(i)%ComponentType=2 | |||
if(item%ComponentType == 1) String(i)%ComponentType=3 | |||
if(item%ComponentType == 3) DownHole%String(i)%ComponentType=0 | |||
if(item%ComponentType == 4) DownHole%String(i)%ComponentType=1 | |||
if(item%ComponentType == 2) DownHole%String(i)%ComponentType=2 | |||
if(item%ComponentType == 1) DownHole%String(i)%ComponentType=3 | |||
!print*, 'item%ComponentType=', item%ComponentType | |||
!print*, 'String(i)%ComponentType=', String(i)%ComponentType | |||
!print*, 'String(i)%StartMd=', String(i)%StartMd | |||
@@ -219,8 +220,8 @@ module CDownHoleVariables | |||
integer :: i = 1 !, j | |||
type(CBopElement), intent(inout), target :: array(count) | |||
type(CBopElement), pointer :: item | |||
if(size(BopElements) > 0) deallocate(BopElements) | |||
allocate(BopElements(count)) | |||
if(size(DownHole%BopElements) > 0) deallocate(DownHole%BopElements) | |||
allocate(DownHole%BopElements(count)) | |||
do i = 1, count | |||
item => array(i) | |||
@@ -229,9 +230,9 @@ module CDownHoleVariables | |||
!call Log_4('item%ElementType', item%ElementType) | |||
!call Log_4('=====================================================') | |||
BopElements(i)%ElementStart = item%ElementStart | |||
BopElements(i)%ElementEnd = item%ElementEnd | |||
BopElements(i)%ElementType = item%ElementType | |||
DownHole%BopElements(i)%ElementStart = item%ElementStart | |||
DownHole%BopElements(i)%ElementEnd = item%ElementEnd | |||
DownHole%BopElements(i)%ElementType = item%ElementType | |||
end do | |||
!if(associated(BopElementsPtr)) call BopElementsPtr(BopElements) | |||
@@ -244,7 +245,7 @@ module CDownHoleVariables | |||
implicit none | |||
integer, intent(in) :: md | |||
call AnnulusPropertyCalculator(md, Density, Pressure, Temperature) | |||
call AnnulusPropertyCalculator(md, DownHole%Density, DownHole%Pressure, DownHole%Temperature) | |||
!ObservationPoint(2)%MeasureDepth = md | |||
@@ -270,7 +271,7 @@ module CDownHoleVariables | |||
implicit none | |||
integer, intent(in) :: md | |||
call StringPropertyCalculator(md, Density, Pressure, Temperature) | |||
call StringPropertyCalculator(md, DownHole%Density, DownHole%Pressure, DownHole%Temperature) | |||
!ObservationPoint(1)%MeasureDepth = md | |||
@@ -198,7 +198,7 @@ module CDataDisplayConsole | |||
implicit none | |||
logical, intent(in) :: v | |||
DataDisplayConsole%DrillingTrippingSelectorSwitch = v | |||
DrillWatchOperationMode = v | |||
Common%DrillWatchOperationMode = v | |||
#ifdef deb | |||
print*, 'DrillingTrippingSelectorSwitch=', DataDisplayConsole%DrillingTrippingSelectorSwitch | |||
#endif | |||
@@ -358,7 +358,8 @@ module COperationScenariosMain | |||
use CTongEnumVariables | |||
use CHoistingVariables | |||
use CKellyConnectionEnumVariables | |||
use CElevatorConnectionEnumVariables | |||
use COperationScenariosVariables | |||
! use CElevatorConnectionEnumVariables | |||
use COperationConditionEnumVariables | |||
use CMouseHoleEnumVariables | |||
implicit none | |||
@@ -84,17 +84,27 @@ module COperationScenariosVariables | |||
implicit none | |||
public | |||
real :: HKL = 63.76 ! Hook And Kelly Length | |||
real :: HL = 17.81 ! Hook Length | |||
real :: PL = 30.0 ! Pipe Length | |||
real :: SL = 90.0 ! Stand Length | |||
real :: LG = 8.0 ! Limit Gap | |||
real :: SG = 3.0 ! Slips Gap | |||
real :: TG = 4.0 ! Tong Gap | |||
real :: RE = 3.0 ! Release | |||
real :: ECG = 2.3 ! Elevator Connection Gap | |||
type::OperationScenarioType | |||
real :: HKL = 63.76 ! Hook And Kelly Length | |||
real :: HL = 17.81 ! Hook Length | |||
real :: PL = 30.0 ! Pipe Length | |||
real :: SL = 90.0 ! Stand Length | |||
real :: LG = 8.0 ! Limit Gap | |||
real :: SG = 3.0 ! Slips Gap | |||
real :: TG = 4.0 ! Tong Gap | |||
real :: RE = 3.0 ! Release | |||
real :: ECG = 2.3 ! Elevator Connection Gap | |||
!moved from enum/CElevatorConnectionEnum | |||
integer :: ElevatorConnection = 0 | |||
type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||
!moved from enum/CKellyConnectionEnum | |||
end type OperationScenarioType | |||
type(OperationScenarioType)::OperationScenario | |||
contains | |||
real(8) function TJH() | |||
@@ -113,4 +123,24 @@ module COperationScenariosVariables | |||
NFC = Get_NearFloorConnection() | |||
end function | |||
subroutine Set_ElevatorConnection(v) | |||
implicit none | |||
integer , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(OperationScenario%ElevatorConnection == v) return | |||
#endif | |||
OperationScenario%ElevatorConnection = v | |||
#ifdef deb | |||
print*, 'OperationScenario%ElevatorConnection=', OperationScenario%ElevatorConnection | |||
#endif | |||
call OperationScenario%OnElevatorConnectionChange%RunAll() | |||
end subroutine | |||
integer function Get_ElevatorConnection() | |||
implicit none | |||
Get_ElevatorConnection = OperationScenario%ElevatorConnection | |||
end function | |||
end module COperationScenariosVariables |
@@ -54,7 +54,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=78 | |||
if (Get_ElevatorPickup() == .false. .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then | |||
call Set_ElevatorConnection(ELEVATOR_LATCH_SINGLE) | |||
return | |||
@@ -63,7 +63,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=79 | |||
if (Get_ElevatorPickup() == .false. .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%SL - OperationScenario%LG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then | |||
call Set_ElevatorConnection(ELEVATOR_LATCH_STAND) | |||
return | |||
@@ -229,7 +229,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=13 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& | |||
!Get_Swing() == SWING_WELL_END .and.& | |||
!Get_TongNotification() .and.& | |||
@@ -245,7 +245,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=14 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||
!Get_Swing() == SWING_WELL_END .and.& | |||
!Get_TongNotification() .and.& | |||
@@ -261,7 +261,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=15 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%SL - OperationScenario%LG) .and.& | |||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& | |||
!Get_Swing() == SWING_WELL_END .and.& | |||
@@ -348,7 +348,7 @@ module CElevatorConnectionEnum | |||
!TOPDRIVE-CODE=73 | |||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||
if ((Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() + OperationScenario%TG)) .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||
Get_LatchLed()) then | |||
@@ -365,7 +365,7 @@ module CElevatorConnectionEnum | |||
!TOPDRIVE-CODE=74 | |||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() - OperationScenario%ECG) .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_ElevatorConnectionPossible() .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | |||
@@ -418,13 +418,13 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=86 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() - OperationScenario%ECG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_LatchLed() .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
Get_ElevatorConnectionPossible() .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection())) then | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection())) then | |||
!call Log_4("OPERATION-CODE=ELEVATOR_LATCH_STRING_BEGIN") | |||
call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN) | |||
@@ -434,7 +434,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=85 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_LatchLed() .and.& | |||
Get_Swing() == SWING_WELL_END) then | |||
@@ -490,7 +490,7 @@ module CElevatorConnectionEnum | |||
!TOPDRIVE-CODE=76 | |||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||
if ((Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() + OperationScenario%TG)) .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND .and.& | |||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||
Get_UnlatchLed()) then | |||
@@ -508,7 +508,7 @@ module CElevatorConnectionEnum | |||
!TOPDRIVE-CODE=77 | |||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() - OperationScenario%ECG) .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
(Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING) .and.& | |||
@@ -527,7 +527,7 @@ module CElevatorConnectionEnum | |||
!TOPDRIVE-CODE=78 | |||
if ((Get_HookHeight() > TL() .and. Get_HookHeight() < (TL() + NFC() + SG)) .and.& | |||
if ((Get_HookHeight() > TL() .and. Get_HookHeight() < (TL() + NFC() + OperationScenario%SG)) .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_TdsSwing() == TDS_SWING_TILT_END .and.& | |||
Get_UnlatchLed() .and.& | |||
@@ -556,9 +556,9 @@ module CElevatorConnectionEnum | |||
#endif | |||
!OPERATION-CODE=89 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() - OperationScenario%ECG) .and.& | |||
(Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection()) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection()) .and.& | |||
Get_UnlatchLed() .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
@@ -572,7 +572,7 @@ module CElevatorConnectionEnum | |||
!OPERATION-CODE=88 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL + RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.& | |||
Get_UnlatchLed() .and.& | |||
@@ -587,7 +587,7 @@ module CElevatorConnectionEnum | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_UnlatchLed() .and.& | |||
Get_HookHeight() >= HL .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SG) .and.& | |||
Get_HookHeight() >= OperationScenario%HL .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%SG) .and.& | |||
!Get_JointConnectionPossible() .and.& | |||
Get_Swing() == SWING_MOUSE_HOLE_END) then | |||
@@ -1,11 +1,12 @@ | |||
module CElevatorConnectionEnumVariables | |||
use CVoidEventHandlerCollection | |||
! use CVoidEventHandlerCollection | |||
implicit none | |||
integer :: ElevatorConnection = 0 | |||
! Mahmood: this variable moved to operationscenariocommon | |||
! integer :: OperationScenario%ElevatorConnection = 0 | |||
! type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||
public | |||
type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||
enum, bind(c) | |||
enumerator ELEVATOR_CONNECTION_NOTHING | |||
@@ -17,48 +18,30 @@ module CElevatorConnectionEnumVariables | |||
enumerator ELEVATOR_LATCH_STAND | |||
end enum | |||
private :: ElevatorConnection | |||
! private :: OperationScenario%ElevatorConnection | |||
contains | |||
subroutine Set_ElevatorConnection(v) | |||
implicit none | |||
integer , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(ElevatorConnection == v) return | |||
#endif | |||
ElevatorConnection = v | |||
#ifdef deb | |||
print*, 'ElevatorConnection=', ElevatorConnection | |||
#endif | |||
call OnElevatorConnectionChange%RunAll() | |||
end subroutine | |||
integer function Get_ElevatorConnection() | |||
implicit none | |||
Get_ElevatorConnection = ElevatorConnection | |||
end function | |||
! subroutine Set_ElevatorConnection_WN(v) | |||
! !DEC$ ATTRIBUTES DLLEXPORT :: Set_ElevatorConnection_WN | |||
! !DEC$ ATTRIBUTES ALIAS: 'Set_ElevatorConnection_WN' :: Set_ElevatorConnection_WN | |||
! implicit none | |||
! integer , intent(in) :: v | |||
! call Set_ElevatorConnection(v) | |||
! end subroutine | |||
subroutine Set_ElevatorConnection_WN(v) | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Set_ElevatorConnection_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Set_ElevatorConnection_WN' :: Set_ElevatorConnection_WN | |||
implicit none | |||
integer , intent(in) :: v | |||
call Set_ElevatorConnection(v) | |||
end subroutine | |||
integer function Get_ElevatorConnection_WN() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Get_ElevatorConnection_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Get_ElevatorConnection_WN' :: Get_ElevatorConnection_WN | |||
implicit none | |||
Get_ElevatorConnection_WN = ElevatorConnection | |||
end function | |||
! integer function Get_ElevatorConnection_WN() | |||
! !DEC$ ATTRIBUTES DLLEXPORT :: Get_ElevatorConnection_WN | |||
! !DEC$ ATTRIBUTES ALIAS: 'Get_ElevatorConnection_WN' :: Get_ElevatorConnection_WN | |||
! implicit none | |||
! Get_ElevatorConnection_WN = OperationScenario%ElevatorConnection | |||
! end function | |||
end module CElevatorConnectionEnumVariables |
@@ -71,7 +71,7 @@ module CKellyConnectionEnum | |||
!OPERATION-CODE=2 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_StringPressure() == 0 .and.& | |||
Get_HookHeight() <= (HKL + Get_NearFloorConnection()) .and.& | |||
Get_HookHeight() <= (OperationScenario%HKL + Get_NearFloorConnection()) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
!Get_TongNotification() .and.& | |||
@@ -1,11 +1,13 @@ | |||
module CKellyConnectionEnumVariables | |||
use CVoidEventHandlerCollection | |||
implicit none | |||
integer :: KellyConnection = 0 | |||
type::KellyConnectionEnumType | |||
integer :: KellyConnection = 0 | |||
type(VoidEventHandlerCollection) :: OnKellyConnectionChange | |||
end type KellyConnectionEnumType | |||
type(KellyConnectionEnumType)::KellyConnectionEnum | |||
! public | |||
public | |||
type(VoidEventHandlerCollection) :: OnKellyConnectionChange | |||
enum, bind(c) | |||
enumerator KELLY_CONNECTION_NOTHING | |||
@@ -13,34 +15,34 @@ module CKellyConnectionEnumVariables | |||
enumerator KELLY_CONNECTION_SINGLE | |||
end enum | |||
private :: KellyConnection | |||
! private :: OperationScenario%KellyConnection | |||
contains | |||
subroutine Set_KellyConnection(v) | |||
use CManifolds, Only: KellyConnected, KellyDisconnected | |||
implicit none | |||
integer , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(KellyConnection == v) return | |||
#endif | |||
#ifdef ExcludeExtraChanges | |||
if(KellyConnectionEnum%KellyConnection == v) return | |||
#endif | |||
KellyConnection = v | |||
KellyConnectionEnum%KellyConnection = v | |||
if(KellyConnection /= KELLY_CONNECTION_STRING) then | |||
if(KellyConnectionEnum%KellyConnection /= KELLY_CONNECTION_STRING) then | |||
call KellyDisconnected() | |||
else | |||
call KellyConnected() | |||
endif | |||
#ifdef deb | |||
print*, 'KellyConnection=', KellyConnection | |||
#endif | |||
call OnKellyConnectionChange%RunAll() | |||
#ifdef deb | |||
print*, 'KellyConnectionEnum%KellyConnection=', KellyConnectionEnum%KellyConnection | |||
#endif | |||
call KellyConnectionEnum%OnKellyConnectionChange%RunAll() | |||
end subroutine | |||
integer function Get_KellyConnection() | |||
implicit none | |||
Get_KellyConnection = KellyConnection | |||
Get_KellyConnection = KellyConnectionEnum%KellyConnection | |||
end function | |||
@@ -48,19 +50,19 @@ module CKellyConnectionEnumVariables | |||
subroutine Set_KellyConnection_WN(v) | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Set_KellyConnection_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Set_KellyConnection_WN' :: Set_KellyConnection_WN | |||
implicit none | |||
integer , intent(in) :: v | |||
call Set_KellyConnection(v) | |||
end subroutine | |||
! subroutine Set_KellyConnection_WN(v) | |||
! !DEC$ ATTRIBUTES DLLEXPORT :: Set_KellyConnection_WN | |||
! !DEC$ ATTRIBUTES ALIAS: 'Set_KellyConnection_WN' :: Set_KellyConnection_WN | |||
! implicit none | |||
! integer , intent(in) :: v | |||
! call Set_KellyConnection(v) | |||
! end subroutine | |||
integer function Get_KellyConnection_WN() | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Get_KellyConnection_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Get_KellyConnection_WN' :: Get_KellyConnection_WN | |||
implicit none | |||
Get_KellyConnection_WN = KellyConnection | |||
end function | |||
! integer function Get_KellyConnection_WN() | |||
! !DEC$ ATTRIBUTES DLLEXPORT :: Get_KellyConnection_WN | |||
! !DEC$ ATTRIBUTES ALIAS: 'Get_KellyConnection_WN' :: Get_KellyConnection_WN | |||
! implicit none | |||
! Get_KellyConnection_WN = OperationScenario%KellyConnection | |||
! end function | |||
end module CKellyConnectionEnumVariables |
@@ -1,19 +1,18 @@ | |||
module CTdsConnectionModesEnumVariables | |||
use CVoidEventHandlerCollection | |||
implicit none | |||
integer :: TdsConnectionModes = 0 | |||
public | |||
type(VoidEventHandlerCollection) :: OnTdsConnectionModesChange | |||
type:: TdsConnectionModesEnumType | |||
integer :: TdsConnectionModes = 0 | |||
type(VoidEventHandlerCollection) :: OnTdsConnectionModesChange | |||
end type TdsConnectionModesEnumType | |||
type(TdsConnectionModesEnumType)::TdsConnectionModesEnum | |||
enum, bind(c) | |||
enumerator TDS_CONNECTION_NOTHING | |||
enumerator TDS_CONNECTION_STRING | |||
enumerator TDS_CONNECTION_SPINE | |||
end enum | |||
private :: TdsConnectionModes | |||
! private :: TdsConnectionModesEnum%TdsConnectionModes | |||
contains | |||
subroutine Set_TdsConnectionModes(v) | |||
@@ -21,25 +20,25 @@ module CTdsConnectionModesEnumVariables | |||
implicit none | |||
integer , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(TdsConnectionModes == v) return | |||
if(TdsConnectionModesEnum%TdsConnectionModes == v) return | |||
#endif | |||
TdsConnectionModes = v | |||
TdsConnectionModesEnum%TdsConnectionModes = v | |||
if(TdsConnectionModes == TDS_CONNECTION_NOTHING) then | |||
if(TdsConnectionModesEnum%TdsConnectionModes == TDS_CONNECTION_NOTHING) then | |||
call KellyDisconnected() | |||
else | |||
call KellyConnected() | |||
endif | |||
#ifdef deb | |||
print*, 'TdsConnectionModes=', TdsConnectionModes | |||
print*, 'TdsConnectionModesEnum%TdsConnectionModes=', TdsConnectionModesEnum%TdsConnectionModes | |||
#endif | |||
call OnTdsConnectionModesChange%RunAll() | |||
call TdsConnectionModesEnum%OnTdsConnectionModesChange%RunAll() | |||
end subroutine | |||
integer function Get_TdsConnectionModes() | |||
implicit none | |||
Get_TdsConnectionModes = TdsConnectionModes | |||
Get_TdsConnectionModes = TdsConnectionModesEnum%TdsConnectionModes | |||
end function | |||
@@ -58,7 +57,7 @@ module CTdsConnectionModesEnumVariables | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Get_TdsConnectionModes_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Get_TdsConnectionModes_WN' :: Get_TdsConnectionModes_WN | |||
implicit none | |||
Get_TdsConnectionModes_WN = TdsConnectionModes | |||
Get_TdsConnectionModes_WN = TdsConnectionModesEnum%TdsConnectionModes | |||
end function | |||
@@ -26,7 +26,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=8 | |||
if (Get_HookHeight() <= (TL() + TJH() - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + TJH() - OperationScenario%ECG) .and.& | |||
Get_ElevatorPickup() == .false. .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING) then | |||
@@ -132,7 +132,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=16 | |||
if (Get_HookHeight() <= (TL() + NFC() + PL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .and.& | |||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING) then | |||
@@ -147,7 +147,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=17 | |||
if (Get_HookHeight() <= (TL() + NFC() + PL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING .and.& | |||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING) then | |||
@@ -172,7 +172,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=19 | |||
if (Get_HookHeight() <= (TL() + NFC() + PL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_ElevatorPickup() == .false. .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE) then | |||
@@ -212,7 +212,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=22 | |||
if (Get_HookHeight() <= (TL() + NFC() + SL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%SL - OperationScenario%ECG) .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .and.& | |||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING) then | |||
@@ -226,7 +226,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=23 | |||
if (Get_HookHeight() <= (TL() + NFC() + SL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%SL - OperationScenario%ECG) .and.& | |||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING .and.& | |||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING) then | |||
@@ -252,7 +252,7 @@ module CTdsElevatorModesEnum | |||
!TOPDRIVE-CODE=25 | |||
if (Get_HookHeight() <= (TL() + NFC() + SL - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() + OperationScenario%SL - OperationScenario%ECG) .and.& | |||
Get_ElevatorPickup() == .false. .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND) then | |||
@@ -1,12 +1,11 @@ | |||
module CTdsElevatorModesEnumVariables | |||
use CVoidEventHandlerCollection | |||
implicit none | |||
integer :: TdsElevatorModes = 0 | |||
public | |||
type(VoidEventHandlerCollection) :: OnTdsElevatorModesChange | |||
type:: TdsElevatorModesEnumType | |||
integer :: TdsElevatorModes = 0 | |||
type(VoidEventHandlerCollection) :: OnTdsElevatorModesChange | |||
end type TdsElevatorModesEnumType | |||
type(TdsElevatorModesEnumType)::TdsElevatorModesEnum | |||
enum, bind(c) | |||
enumerator TDS_ELEVATOR_CONNECTION_NOTHING | |||
enumerator TDS_ELEVATOR_CONNECTION_STRING | |||
@@ -17,22 +16,22 @@ module CTdsElevatorModesEnumVariables | |||
enumerator TDS_ELEVATOR_LATCH_STAND | |||
end enum | |||
private :: TdsElevatorModes | |||
! private :: TdsElevatorModesEnum%TdsElevatorModes | |||
contains | |||
subroutine Set_TdsElevatorModes(v) | |||
implicit none | |||
integer , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(TdsElevatorModes == v) return | |||
if(TdsElevatorModesEnum%TdsElevatorModes == v) return | |||
#endif | |||
TdsElevatorModes = v | |||
call OnTdsElevatorModesChange%RunAll() | |||
TdsElevatorModesEnum%TdsElevatorModes = v | |||
call TdsElevatorModesEnum%OnTdsElevatorModesChange%RunAll() | |||
end subroutine | |||
integer function Get_TdsElevatorModes() | |||
implicit none | |||
Get_TdsElevatorModes = TdsElevatorModes | |||
Get_TdsElevatorModes = TdsElevatorModesEnum%TdsElevatorModes | |||
end function | |||
@@ -52,7 +51,7 @@ module CTdsElevatorModesEnumVariables | |||
!DEC$ ATTRIBUTES DLLEXPORT :: Get_TdsElevatorModes_WN | |||
!DEC$ ATTRIBUTES ALIAS: 'Get_TdsElevatorModes_WN' :: Get_TdsElevatorModes_WN | |||
implicit none | |||
Get_TdsElevatorModes_WN = TdsElevatorModes | |||
Get_TdsElevatorModes_WN = TdsElevatorModesEnum%TdsElevatorModes | |||
end function | |||
@@ -46,16 +46,7 @@ module CCloseKellyCockLedNotification | |||
print*, 'Evaluate_CloseKellyCockLed=TopDrive' | |||
#endif | |||
endif | |||
if (Hoisting%DriveType == Kelly_DriveType) then | |||
#ifdef OST | |||
print*, 'Evaluate_CloseKellyCockLed=Kelly' | |||
@@ -18,7 +18,7 @@ module CLatchLedNotification | |||
!TOPDRIVE-CODE=44 | |||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() - OperationScenario%ECG) .and.& | |||
Get_ElevatorConnectionPossible() .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -41,7 +41,7 @@ module CLatchLedNotification | |||
!TOPDRIVE-CODE=45 | |||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||
if ((Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() + OperationScenario%TG)) .and.& | |||
GetStandRack() > 0 .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
@@ -64,7 +64,7 @@ module CLatchLedNotification | |||
!TOPDRIVE-CODE=46 | |||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||
if ((Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() + OperationScenario%TG)) .and.& | |||
Get_ElevatorConnectionPossible() .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -113,7 +113,7 @@ module CLatchLedNotification | |||
!OPERATION-CODE=36 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() - OperationScenario%ECG) .and.& | |||
Get_ElevatorConnectionPossible() .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
@@ -137,7 +137,7 @@ module CLatchLedNotification | |||
!OPERATION-CODE=37 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_StandRack() > 0 .and.& | |||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -125,7 +125,7 @@ module CSlipsNotification | |||
! call OnSlackOffChange%Add(Evaluate_SlipsNotification) | |||
! call OnZeroStringSpeedChange%Add(Evaluate_SlipsNotification) | |||
! call OnNearFloorConnectionChange%Add(Evaluate_SlipsNotification) | |||
! call OnElevatorConnectionChange%Add(Evaluate_SlipsNotification) | |||
! call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_SlipsNotification) | |||
! call OnKellyConnectionChange%Add(Evaluate_SlipsNotification) | |||
! call OnSlipsChange%Add(Evaluate_SlipsNotification) | |||
@@ -35,7 +35,7 @@ module CSwingLedNotification | |||
!OPERATION-CODE=22 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
(Get_Swing() /= SWING_WELL_BEGIN .and.& | |||
@@ -50,7 +50,7 @@ module CSwingLedNotification | |||
!OPERATION-CODE=23 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + PL) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + LG + PL) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL) .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%LG + OperationScenario%PL) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
(Get_Swing() /= SWING_WELL_BEGIN .and.& | |||
@@ -65,7 +65,7 @@ module CSwingLedNotification | |||
!OPERATION-CODE=24 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HKL + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& | |||
(Get_Swing() /= SWING_WELL_BEGIN .and.& | |||
@@ -79,7 +79,7 @@ module CSwingLedNotification | |||
!OPERATION-CODE=25 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection() + PL) .and. Get_HookHeight() <= (HKL + Get_NearFloorConnection() + LG + PL) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%PL) .and. Get_HookHeight() <= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%LG + OperationScenario%PL) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
(Get_Swing() /= SWING_WELL_BEGIN .and.& | |||
@@ -19,8 +19,8 @@ module CTongNotification | |||
!TOPDRIVE-CODE=50 | |||
if (((Get_HookHeight() >= (TL() + PL - ECG + NFC() - RE) .and. Get_HookHeight() <= (TL() + NFC() + PL - ECG + TG)) .or.& | |||
(Get_HookHeight() >= (TL() + SL - ECG + NFC() - RE) .and. Get_HookHeight() <= (TL() + NFC() + SL - ECG + TG))).and.& | |||
if (((Get_HookHeight() >= (TL() + OperationScenario%PL - OperationScenario%ECG + NFC() - OperationScenario%RE) .and. Get_HookHeight() <= (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG + OperationScenario%TG)) .or.& | |||
(Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() - OperationScenario%RE) .and. Get_HookHeight() <= (TL() + NFC() + OperationScenario%SL - OperationScenario%ECG + OperationScenario%TG))).and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
((Get_Tong() /= TONG_BREAKOUT_BEGIN .and.& | |||
@@ -95,8 +95,8 @@ module CTongNotification | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
!((Get_HookHeight() >= 65.0 .and. Get_HookHeight() <= 70.0) .or.& | |||
! (Get_HookHeight() >= 96.0 .and. Get_HookHeight() <= 101.0)).and.& | |||
((Get_HookHeight() >= (HKL + Get_NearFloorConnection() - RE) .and. Get_HookHeight() <= (HKL + Get_NearFloorConnection() + TG)) .or.& | |||
(Get_HookHeight() >= (HKL + Get_NearFloorConnection() + PL -RE) .and. Get_HookHeight() <= (HKL + Get_NearFloorConnection() + TG + PL))).and.& | |||
((Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection() - OperationScenario%RE) .and. Get_HookHeight() <= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%TG)) .or.& | |||
(Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%PL -OperationScenario%RE) .and. Get_HookHeight() <= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%TG + OperationScenario%PL))).and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
@@ -189,8 +189,8 @@ module CTongNotification | |||
!OPERATION-CODE=50 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
((Get_HookHeight() >= (HL + PL - ECG + Get_NearFloorConnection() - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL - ECG + TG)) .or.& | |||
(Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection() - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + TG - ECG + SL))).and.& | |||
((Get_HookHeight() >= (OperationScenario%HL + OperationScenario%PL - OperationScenario%ECG + Get_NearFloorConnection() - OperationScenario%RE) .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL - OperationScenario%ECG + OperationScenario%TG)) .or.& | |||
(Get_HookHeight() >= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection() - OperationScenario%RE) .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%TG - OperationScenario%ECG + OperationScenario%SL))).and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& | |||
@@ -275,8 +275,8 @@ module CTongNotification | |||
call OnHookHeightChange%Add(Evaluate_TongNotification) | |||
call OnJointConnectionPossibleChange%Add(Evaluate_TongNotification) | |||
call OnSingleSetInMouseHoleChange%Add(Evaluate_TongNotification) | |||
call OnElevatorConnectionChange%Add(Evaluate_TongNotification) | |||
call OnKellyConnectionChange%Add(Evaluate_TongNotification) | |||
call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_TongNotification) | |||
call KellyConnectionEnum%OnKellyConnectionChange%Add(Evaluate_TongNotification) | |||
call OnSwingChange%Add(Evaluate_TongNotification) | |||
call OnSlipsChange%Add(Evaluate_TongNotification) | |||
@@ -17,7 +17,7 @@ module CUnlatchLedNotification | |||
!TOPDRIVE-CODE=47 | |||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||
if (Get_HookHeight() <= (TL() + NFC() - OperationScenario%ECG) .and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -38,7 +38,7 @@ module CUnlatchLedNotification | |||
!TOPDRIVE-CODE=48 | |||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||
if ((Get_HookHeight() >= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + OperationScenario%SL - OperationScenario%ECG + NFC() + OperationScenario%TG)) .and.& | |||
GetStandRack() > 80 .and.& | |||
Get_JointConnectionPossible() == .false. .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
@@ -61,7 +61,7 @@ module CUnlatchLedNotification | |||
!TOPDRIVE-CODE=49 | |||
if ((Get_HookHeight() >= TL() .and. Get_HookHeight() <= (TL() + NFC() + SG)) .and.& | |||
if ((Get_HookHeight() >= TL() .and. Get_HookHeight() <= (TL() + NFC() + OperationScenario%SG)) .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.& | |||
@@ -101,7 +101,7 @@ module CUnlatchLedNotification | |||
!OPERATION-CODE=40 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||
Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() - OperationScenario%ECG) .and.& | |||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -130,7 +130,7 @@ module CUnlatchLedNotification | |||
!OPERATION-CODE=41 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (OperationScenario%HL + OperationScenario%SL - OperationScenario%ECG + Get_NearFloorConnection() + OperationScenario%LG) .and.& | |||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL + RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
@@ -157,7 +157,7 @@ module CUnlatchLedNotification | |||
!OPERATION-CODE=42 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= HL .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SG) .and.& | |||
Get_HookHeight() >= OperationScenario%HL .and. Get_HookHeight() <= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%SG) .and.& | |||
(Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.& | |||
Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.& | |||
@@ -211,7 +211,7 @@ module CUnlatchLedNotification | |||
call OnOperationConditionChange%Add(Evaluate_UnlatchLed) | |||
call OnHookHeightChange%Add(Evaluate_UnlatchLed) | |||
call OnStandRackChanged%Add(Evaluate_UnlatchLed) | |||
call OnElevatorConnectionChange%Add(Evaluate_UnlatchLed) | |||
call OperationScenario%OnElevatorConnectionChange%Add(Evaluate_UnlatchLed) | |||
call OnSwingChange%Add(Evaluate_UnlatchLed) | |||
call OnSlipsChange%Add(Evaluate_UnlatchLed) | |||
call OnLatchLedChange%Add(Evaluate_UnlatchLed) | |||
@@ -32,7 +32,7 @@ module CStandRack | |||
subroutine Subscribe_StandRack() | |||
use CCommonVariables | |||
implicit none | |||
call OnStandRackChange%AssignTo(Set_StandRack) | |||
call Common%OnStandRackChange%AssignTo(Set_StandRack) | |||
end subroutine | |||
end module CStandRack |
@@ -70,7 +70,7 @@ module CSwingEnum | |||
!OPERATION-CODE=26 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection() + PL) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%PL) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
Get_SwingLed() .and.& | |||
@@ -85,7 +85,7 @@ module CSwingEnum | |||
!OPERATION-CODE=27 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection() + PL) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection() + OperationScenario%PL) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||
Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||
Get_SwingLed()) then | |||
@@ -99,7 +99,7 @@ module CSwingEnum | |||
!OPERATION-CODE=28 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection()) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection()) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
Get_SwingLed()) then | |||
@@ -112,7 +112,7 @@ module CSwingEnum | |||
!OPERATION-CODE=29 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + SG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + OperationScenario%SG) .and.& | |||
Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& | |||
Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||
Get_SwingLed()) then | |||
@@ -124,7 +124,7 @@ module CSwingEnum | |||
!OPERATION-CODE=30 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= (HKL + Get_NearFloorConnection()) .and.& | |||
Get_HookHeight() >= (OperationScenario%HKL + Get_NearFloorConnection()) .and.& | |||
Get_Swing() == SWING_RAT_HOLE_END .and.& | |||
Get_SwingLed()) then | |||
@@ -136,7 +136,7 @@ module CSwingEnum | |||
!OPERATION-CODE=31 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection()) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection()) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
Get_SwingLed()) then | |||
@@ -163,7 +163,7 @@ module CSwingEnum | |||
!OPERATION-CODE=33 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
(Get_HookHeight() >= (HL + Get_NearFloorConnection()) .and. Get_HookHeight() <= 27.41) .and.& | |||
(Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection()) .and. Get_HookHeight() <= 27.41) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||
Get_Swing() == SWING_MOUSE_HOLE_END .and.&!Get_Swing() == SWING_MOUSE_HOLE_END .and.&!Get_Swing() /= SWING_WELL_END | |||
Get_SwingLed()) then | |||
@@ -176,7 +176,7 @@ module CSwingEnum | |||
!OPERATION-CODE=34 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + PL - ECG) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_Swing() == SWING_WELL_END .and.& | |||
Get_SwingLed()) then | |||
@@ -191,7 +191,7 @@ module CSwingEnum | |||
!OPERATION-CODE=35 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + PL - ECG + RE) .and.& | |||
Get_HookHeight() >= (OperationScenario%HL + Get_NearFloorConnection() + OperationScenario%PL - OperationScenario%ECG + OperationScenario%RE) .and.& | |||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||
Get_SwingLed()) then | |||
@@ -83,7 +83,7 @@ module CTdsSwingEnum | |||
!TOPDRIVE-CODE=42 | |||
if (Get_HookHeight() > (TL() + NFC() + PL - ECG) .and.& | |||
if (Get_HookHeight() > (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_SwingTiltPermission() .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||
@@ -98,7 +98,7 @@ module CTdsSwingEnum | |||
!TOPDRIVE-CODE=43 | |||
if (Get_HookHeight() > (TL() + NFC() + PL - ECG) .and.& | |||
if (Get_HookHeight() > (TL() + NFC() + OperationScenario%PL - OperationScenario%ECG) .and.& | |||
Get_SwingOffPermission() .and.& | |||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE .and.& | |||
Get_TdsSwing() == TDS_SWING_TILT_END .and.& | |||
@@ -18,8 +18,6 @@ CSharp: | |||
PathGeneration | |||
WellSurveyData | |||
MudProperties | |||
Equipments: | |||
ControlPanel: | |||
BopControlPanel | |||
@@ -36,3 +34,10 @@ CSharp: | |||
Manifold | |||
Tanks: | |||
Tank | |||
Common: | |||
Common | |||
Lesson | |||
DownHole: | |||
DownHole | |||
OperationScenario: | |||
OperationScenarioCommon: Constants? or Variables? |
@@ -84,27 +84,27 @@ subroutine Drawworks_INPUTS | |||
if ( Hoisting%DriveType==1 .and. Get_OperationCondition()==OPERATION_DRILL ) then | |||
if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then | |||
DW_DrillModeCond = 1 | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+HKL-RE ![ft] HKL=63.76=Kelly Ass. Height , RE=Release | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+OperationScenario%HKL-OperationScenario%RE ![ft] HKL=63.76=Kelly Ass. Height , RE=Release | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection()==KELLY_CONNECTION_SINGLE ) then | |||
DW_DrillModeCond = 2 | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+HKL+PL-RE ![ft] PL=30=Pipe Lenght | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+OperationScenario%HKL+OperationScenario%PL-OperationScenario%RE ![ft] PL=30=Pipe Lenght | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection() == KELLY_CONNECTION_STRING ) then | |||
DW_DrillModeCond = 3 | |||
Drawworks%min_Hook_Height = 21.44d0-RE ![ft] ?????????? check 21.44=(TD_KellyConst-TD_KellyElementConst) | |||
Drawworks%min_Hook_Height = 21.44d0-OperationScenario%RE ![ft] ?????????? check 21.44=(TD_KellyConst-TD_KellyElementConst) | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then | |||
DW_DrillModeCond = 4 | |||
Drawworks%min_Hook_Height = 66.d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 66.d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_SINGLE ) then | |||
DW_DrillModeCond = 5 | |||
Drawworks%min_Hook_Height = 65.1d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 65.1d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
else if ( Get_Swing()==SWING_RAT_HOLE_END ) then | |||
DW_DrillModeCond = 6 | |||
Drawworks%min_Hook_Height = 66.d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 66.d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 120.d0 ![ft] | |||
end if | |||
else if ( Hoisting%DriveType==1 .and. Get_OperationCondition()==OPERATION_TRIP ) then | |||
@@ -114,27 +114,27 @@ subroutine Drawworks_INPUTS | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND ) then | |||
DW_DrillModeCond = 8 | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+HL+SL-(3.d0*RE) ![ft] HL=17.81=Hook Assy , SL=90=Stand Length , 3: chon meghdari az toole loole(tool joint) dakhele elevator gharar migirad | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+OperationScenario%HL+OperationScenario%SL-(3.d0*OperationScenario%RE) ![ft] HL=17.81=Hook Assy , SL=90=Stand Length , 3: chon meghdari az toole loole(tool joint) dakhele elevator gharar migirad | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE ) then | |||
DW_DrillModeCond = 9 | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+HL+PL-(3.d0*RE) ![ft] 3: chon meghdari az toole loole(tool joint) balaye elevator mimanad | |||
Drawworks%min_Hook_Height = TD_TopJointHeight+OperationScenario%HL+OperationScenario%PL-(3.d0*OperationScenario%RE) ![ft] 3: chon meghdari az toole loole(tool joint) balaye elevator mimanad | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING ) then | |||
DW_DrillModeCond = 10 | |||
Drawworks%min_Hook_Height = 18.5d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 18.5d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING ) then | |||
DW_DrillModeCond = 11 | |||
Drawworks%min_Hook_Height = 19.38d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 19.38d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE ) then | |||
DW_DrillModeCond = 12 | |||
Drawworks%min_Hook_Height = 17.73d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 17.73d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_RAT_HOLE_END ) then | |||
DW_DrillModeCond = 13 | |||
Drawworks%min_Hook_Height = 27.41d0-RE ![ft] | |||
Drawworks%min_Hook_Height = 27.41d0-OperationScenario%RE ![ft] | |||
Drawworks%max_Hook_Height = 140.d0 ![ft] | |||
else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING ) then | |||
DW_DrillModeCond = 14 | |||
@@ -9,6 +9,7 @@ subroutine Drawworks_Solver | |||
Use CWarningsVariables | |||
Use COperationConditionEnumVariables | |||
Use CSlipsEnumVariables | |||
Use COperationScenariosVariables, only: Get_ElevatorConnection | |||
Use CElevatorConnectionEnumVariables | |||
Use CTdsConnectionModesEnumVariables | |||
Use CTdsElevatorModesEnumVariables | |||
@@ -8,6 +8,7 @@ subroutine Drawworks_Solver_FreeTractionMotor | |||
Use COperationConditionEnumVariables | |||
Use CSlipsEnumVariables | |||
Use CElevatorConnectionEnumVariables | |||
use COperationScenariosVariables, only: Get_ElevatorConnection | |||
Use CTdsConnectionModesEnumVariables | |||
Use CTdsElevatorModesEnumVariables | |||
Use Drawworks_VARIABLES | |||
@@ -79,7 +79,7 @@ subroutine Instructor_CirculationMud_Edit ! is called in subroutine Circulat | |||
if ( AnnDrillMud == .true. .and. (Rate_of_Penetration>0. .and. DeltaVolumeOp>0.0) ) then | |||
if ( DownHole%AnnDrillMud == .true. .and. (Rate_of_Penetration>0. .and. DeltaVolumeOp>0.0) ) then | |||
do imud= 1, Ann_Density%Length() | |||
@@ -93,7 +93,7 @@ subroutine Instructor_CirculationMud_Edit ! is called in subroutine Circulat | |||
endif | |||
if ( AnnCirculateMud == .true. ) then | |||
if ( DownHole%AnnCirculateMud == .true. ) then | |||
do imud= 1, Ann_Density%Length() | |||
@@ -69,7 +69,7 @@ IF (WellHeadOpen .OR. NoGasPocket == 0) THEN !! (mud circulation is normal we | |||
IF (WellHeadWasOpen == .FALSE. .AND. NoGasPocket > 0 .AND. KickIteration == 1) THEN | |||
IF (ChokeKroneckerDelta == 1) THEN ! flow on choke line | |||
IF (TotalOpenChokeArea < 0.01 * ChokeAreaFullyOpen) THEN | |||
WRITE (*,*) 'density , TotalOpenChokeArea' , density, TotalOpenChokeArea | |||
WRITE (*,*) 'density , TotalOpenChokeArea' , DownHole%Density, TotalOpenChokeArea | |||
TotalOpenChokeArea = 0.01 * ChokeAreaFullyOpen | |||
END IF | |||
Kchoke = (ChokeDensity / ((2.0 * 89158.0) * (0.26 * 0.61 * TotalOpenChokeArea)**2)) * 4.0 ! *4.d0: seyyed gofte | |||
@@ -42,8 +42,8 @@ SUBROUTINE FlowStartup | |||
WellHeadWasOpen = .TRUE. | |||
BackPressure = 0.0 | |||
GasKickPumpFlowRate = 0.0 | |||
KickVolume = 0.0 | |||
InfluxRate = 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 | |||
@@ -18,7 +18,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
USE CDataDisplayConsoleVariables !, CasingPressureDataDisplay=> CasingPressure | |||
USE CDrillWatchVariables | |||
USE CShoeVariables | |||
USE CDownHoleVariables , CasingPressureDownhole => CasingPressure | |||
USE CDownHoleVariables! , OperationScenarioCommon%ElevatorConnection => DownHole%CasingPressure | |||
USE TD_WellGeometry | |||
USE CManifolds | |||
USE VARIABLES | |||
@@ -75,7 +75,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
!IF (NoGasPocket > 0) THEN ! mud exprience no comressibility | |||
!IF (KickVolume > 2.0) THEN | |||
IF ( (KickVolume > 2.0) .or. (NoGasPocket>1) .or. (any(FlowEl(OpenholeFirstEl:NumbEl)%Materialtype==1)) .or. (Rate_of_Penetration > 0.0) ) THEN | |||
IF ( (DownHole%KickVolume > 2.0) .or. (NoGasPocket>1) .or. (any(FlowEl(OpenholeFirstEl:NumbEl)%Materialtype==1)) .or. (Rate_of_Penetration > 0.0) ) THEN | |||
AnnCompressedMudVol = 0.0 | |||
AnnDeltaPDueToCompressibility = 0.0 | |||
@@ -416,7 +416,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
PressureGauges(1) = 0.0 | |||
!CALL Set_StandPipePressure(0.0d0) !StandPipePressureGauge = 0 | |||
END IF | |||
DrillPipePressure = real(PressureGauges(1), 8) | |||
DownHole%DrillPipePressure = real(PressureGauges(1), 8) | |||
!WRITE (*,*) 'Drillpipe Pressure', PressureGauges(1) | |||
!!!!!!!!!!!!!!!!! 2- Casing pressure gauge PressureGauge(2) | |||
@@ -464,7 +464,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
! PressureGauges(2) = 0.0 | |||
!END IF | |||
CALL Set_CasingPressure(real(PressureGauges(2) , 8)) ! for display console | |||
CasingPressureDownhole = real(PressureGauges(2) , 8) | |||
Downhole%CasingPressure = real(PressureGauges(2) , 8) | |||
!IF (PressureGauges(2) > 3000.0) THEN | |||
! !CALL Error(' High Casing Pressure') | |||
!END IF | |||
@@ -488,7 +488,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
BottomHolePress = BottomHolePressureDelay%Array(PressureTimeStepDelay(2)) | |||
BottomHolePressure = REAL(PressureGauges(3) , 8) | |||
DownHole%BottomHolePressure = REAL(PressureGauges(3) , 8) | |||
!!!!!!!!!!!!!!!!! 4- Under Bit Pressure PressureGauges(4) | |||
PressureGauges(4) = FlowEl(AnnulusFirstEl)%StartPress | |||
@@ -532,7 +532,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
!PressureGauges(5) = INT(ShoePressureDelay%Array(PressureTimeStepDelay(3))) | |||
ShoePressure = real(PressureGauges(5), 8) | |||
DownHole%ShoePressure = real(PressureGauges(5), 8) | |||
@@ -650,7 +650,7 @@ SUBROUTINE PressureHorizAndStringDistribution | |||
!WRITE (*,*) ' SecondaryKickWeight', SecondaryKickWeight | |||
!WRITE (*,*) ' SecondaryKickVol', SecondaryKickVol | |||
SecondKickVolume = SecondaryKickVol | |||
DownHole%SecondKickVolume = SecondaryKickVol | |||
@@ -598,7 +598,7 @@ SUBROUTINE GasPocketFlowElementTransformer | |||
!WRITE (*,*) 'Kick density (ppg)=' , GasPocketDensity(1) | |||
InfluxRate = MAX(((KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1))) / GasPocketDensity%Array(1) * ConvMinToSec) , 0.0) | |||
DownHole%InfluxRate = MAX(((KickmdotACoef * (KickmdotBCoef - GasPocketNewPress%Array(1))) / GasPocketDensity%Array(1) * ConvMinToSec) , 0.0) | |||
!WRITE (*,*) ' InfluxRate (gpm) =', InfluxRate | |||
i = OpenholeFirstEl - 1 | |||
@@ -691,7 +691,7 @@ SUBROUTINE GasPocketFlowElementTransformer | |||
KickVolume = INT(SUM(GasPocketOldVol%Array(:)) * convft3toUSgal / 42. * 10.0) / 10.0 | |||
DownHole%KickVolume = INT(SUM(GasPocketOldVol%Array(:)) * convft3toUSgal / 42. * 10.0) / 10.0 | |||
!WRITE (*,*) ' Gas Kick Pressure (psi) = ' , GasPocketOldPress(1) , INT((GasPocketNewVol(1) / GasPocketOldVol(1)) * 1000.d0) / 1000.d0 | |||
@@ -758,8 +758,8 @@ SUBROUTINE RemoveGasPocket(ilocal) | |||
CALL GasPocketWeight%Empty | |||
CALL GasPocketDensity%Empty | |||
InfluxRate = 0.0 | |||
KickVolume = 0.0 | |||
DownHole%InfluxRate = 0.0 | |||
DownHole%KickVolume = 0.0 | |||
END IF | |||
@@ -76,14 +76,14 @@ SUBROUTINE FormationInformationCalculator | |||
end if | |||
!PermeabilityExposedHeight = KickFormLength * FormationPermeability | |||
PermeabilityExposedHeight = FluidFlowCounter - MudSys_timeCounter | |||
DownHole%PermeabilityExposedHeight = FluidFlowCounter - MudSys_timeCounter | |||
!==================================================== | |||
! Reservoir Data | |||
!==================================================== | |||
FormPermeability = Reservoir%FormationPermeability ! [mD] | |||
FormPressure = TD_WellTotalVerticalLength * Formation%Formations(Reservoir%FormationNo)%PorePressureGradient ![psia] | |||
FormationPressure = INT(FormPressure) | |||
DownHole%FormationPressure = INT(FormPressure) | |||
!CALL Log_2('FormPressure =' , FormPressure) | |||
!print*, 'Formations(FormationNo)%PorePressureGradient=', Formations(FormationNo)%PorePressureGradient | |||
!print * , 'FormationNo=' , FormationNo | |||
@@ -6,6 +6,7 @@ subroutine TD_AddComponents | |||
Use CIbopEnumVariables | |||
Use COperationConditionEnumVariables | |||
Use CKellyConnectionEnumVariables | |||
use COperationScenariosVariables, only: Get_ElevatorConnection | |||
Use CElevatorConnectionEnumVariables | |||
Use CHoistingVariables | |||
Use CTdsConnectionModesEnumVariables | |||
@@ -7,6 +7,7 @@ subroutine TD_RemoveComponents | |||
Use COperationConditionEnumVariables | |||
Use CKellyConnectionEnumVariables | |||
Use CElevatorConnectionEnumVariables | |||
Use COperationScenariosVariables | |||
Use CTdsConnectionModesEnumVariables | |||
Use CTdsElevatorModesEnumVariables | |||
Use CHoistingVariables | |||
@@ -67,7 +67,7 @@ subroutine TD_StringConnectionModes | |||
TD_HookHeight = DW_TDHookHeight ! unit: [ft] | |||
TD_ElevatorConst = 17.985 ! [ft] Elevator Length(14.84) ????????????????? adad ha daghigh shavand | |||
TD_ElevatorECG = ECG ! [ft] | |||
TD_ElevatorECG = OperationScenario%ECG ! [ft] | |||
TD_KellyConst = 63.280d0 ! [ft] Kelly Length(61.74) + Safety Valve Length(1.54) | |||
TD_KellyElementConst = 41.840d0 ! [ft] Kelly Element Length(40.3) + Safety Valve Length(1.54) | |||
TD_TDSLength = 24.08d0 !??????????????????? ! [ft] | |||