@@ -11,7 +11,7 @@ module CFormation | |||||
integer :: i | integer :: i | ||||
type(CFormationItem), intent(inout), target :: array(count) | type(CFormationItem), intent(inout), target :: array(count) | ||||
type(CFormationItem), pointer :: item | type(CFormationItem), pointer :: item | ||||
FormationCount = count | |||||
Formation%Count = count | |||||
if(size(Formation%Formations) > 0) then | if(size(Formation%Formations) > 0) then | ||||
deallocate(Formation%Formations) | deallocate(Formation%Formations) | ||||
end if | end if | ||||
@@ -12,10 +12,12 @@ module CFormationVariables | |||||
real(8) :: ThresholdWeight | real(8) :: ThresholdWeight | ||||
real(8) :: PorePressureGradient | real(8) :: PorePressureGradient | ||||
end type CFormationItem | end type CFormationItem | ||||
Type::FormationType | Type::FormationType | ||||
integer :: Formation%Count = 0 | |||||
type(CFormationItem), allocatable :: Formation%Formations(:) | |||||
integer :: Count = 0 | |||||
type(CFormationItem), allocatable :: Formations(:) | |||||
End type FormationType | End type FormationType | ||||
Type(FormationType) :: Formation | Type(FormationType) :: Formation | ||||
contains | contains | ||||
end module CFormationVariables | end module CFormationVariables |
@@ -9,6 +9,6 @@ module CShoeVariables | |||||
real(8) :: Breakdown | real(8) :: Breakdown | ||||
real(8) :: FracturePropagation | real(8) :: FracturePropagation | ||||
logical :: InactiveFracture | logical :: InactiveFracture | ||||
End type Reservoir | |||||
End type ShoeType | |||||
Type(ShoeType)::Shoe | Type(ShoeType)::Shoe | ||||
end module CShoeVariables | end module CShoeVariables |
@@ -23,9 +23,9 @@ module CBopStackVariables | |||||
real(8) :: AnnularPreventerClose | real(8) :: AnnularPreventerClose | ||||
real(8) :: RamStringDrag | real(8) :: RamStringDrag | ||||
real(8) :: AnnularStringDrag | real(8) :: AnnularStringDrag | ||||
real(8) :: ChokeLineLength | real(8) :: ChokeLineLength | ||||
real(8) :: ChokeLineId | real(8) :: ChokeLineId | ||||
End Type BopStackType | |||||
End Type BopStackSpecificationType | |||||
Type(BopStackSpecificationType)::BopStackSpecification | Type(BopStackSpecificationType)::BopStackSpecification | ||||
end module CBopStackVariables | end module CBopStackVariables |
@@ -11,7 +11,7 @@ module CPathGeneration | |||||
integer :: i | integer :: i | ||||
type(CPathGenerationItem), intent(inout), target :: array(count) | type(CPathGenerationItem), intent(inout), target :: array(count) | ||||
type(CPathGenerationItem), pointer :: item | type(CPathGenerationItem), pointer :: item | ||||
PathGenerationCount = count | |||||
PathGeneration%ItemCount = count | |||||
if(size(PathGeneration%Items) > 0) then | if(size(PathGeneration%Items) > 0) then | ||||
deallocate(PathGeneration%Items) | deallocate(PathGeneration%Items) | ||||
end if | end if | ||||
@@ -20,11 +20,11 @@ module CPathGenerationVariables | |||||
Type :: PathGenerationType | Type :: PathGenerationType | ||||
integer :: ItemCount = 0 | integer :: ItemCount = 0 | ||||
type(CPathGenerationItem), allocatable :: Items(:) | |||||
type(CPathGenerationItem), allocatable :: Items(:) | |||||
integer :: DataPointsCount = 0 | integer :: DataPointsCount = 0 | ||||
type(CDataPointItem), allocatable :: DataPoints(:) | type(CDataPointItem), allocatable :: DataPoints(:) | ||||
End type PathGenerationType | End type PathGenerationType | ||||
Type(PathGenerationType)::PathGeneration | Type(PathGenerationType)::PathGeneration | ||||
end module CPathGenerationVariables | end module CPathGenerationVariables |
@@ -11,7 +11,7 @@ module CWellSurveyData | |||||
integer :: i | integer :: i | ||||
type(CSurveyDataItem), intent(inout), target :: array(count) | type(CSurveyDataItem), intent(inout), target :: array(count) | ||||
type(CSurveyDataItem), pointer :: item | type(CSurveyDataItem), pointer :: item | ||||
SurveyDataCount = count | |||||
WellSurveyData%Count = count | |||||
if(size(WellSurveyData%Items) > 0) then | if(size(WellSurveyData%Items) > 0) then | ||||
deallocate(WellSurveyData%Items) | deallocate(WellSurveyData%Items) | ||||
end if | end if | ||||
@@ -6,10 +6,7 @@ module CCommonVariables | |||||
! Input vars | ! Input vars | ||||
integer :: StandRack | integer :: StandRack | ||||
type(IntegerEventHandler) :: OnStandRackChange | type(IntegerEventHandler) :: OnStandRackChange | ||||
! Output vars | ! Output vars | ||||
logical :: DrillWatchOperationMode | logical :: DrillWatchOperationMode | ||||
contains | contains | ||||
end module CCommonVariables | end module CCommonVariables |
@@ -5,7 +5,7 @@ module CHookVariables | |||||
Type :: HookType | Type :: HookType | ||||
real :: HookHeight_S = 0.0 | real :: HookHeight_S = 0.0 | ||||
real :: HookHeight | real :: HookHeight | ||||
type(RealEventHandlerCollection) :: Hook%OnHookHeightChange | |||||
type(RealEventHandlerCollection) :: OnHookHeightChange | |||||
end type HookType | end type HookType | ||||
Type(HookType)::Hook | Type(HookType)::Hook | ||||
@@ -2,7 +2,7 @@ module CStandPipeManifoldVariables | |||||
implicit none | implicit none | ||||
public | public | ||||
Type::StandPipeManifold | |||||
Type::StandPipeManifoldType | |||||
! Input vars | ! Input vars | ||||
logical :: StandPipeManifoldValve1 | logical :: StandPipeManifoldValve1 | ||||
logical :: StandPipeManifoldValve2 | logical :: StandPipeManifoldValve2 | ||||
@@ -24,5 +24,5 @@ module CStandPipeManifoldVariables | |||||
real(8) :: StandPipeGauge1 | real(8) :: StandPipeGauge1 | ||||
real(8) :: StandPipeGauge2 | real(8) :: StandPipeGauge2 | ||||
End type StandPipeManifoldType | End type StandPipeManifoldType | ||||
contains | |||||
type(StandPipeManifoldType)::StandPipeManifold | |||||
end module CStandPipeManifoldVariables | end module CStandPipeManifoldVariables |
@@ -11,9 +11,9 @@ module CTopDrivePanel | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTdsPowerState' :: SetTopDriveTdsPowerState | !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTdsPowerState' :: SetTopDriveTdsPowerState | ||||
implicit none | implicit none | ||||
integer, intent(in) :: v | integer, intent(in) :: v | ||||
TopDriveTdsPowerState = v | |||||
TopDrivePanel%TopDriveTdsPowerState = v | |||||
#ifdef deb | #ifdef deb | ||||
call Log_3( 'TopDriveTdsPowerState=', TopDriveTdsPowerState) | |||||
call Log_3( 'TopDriveTdsPowerState=', TopDrivePanel%TopDriveTdsPowerState) | |||||
#endif | #endif | ||||
end subroutine | end subroutine | ||||
@@ -71,8 +71,8 @@ module CTopDrivePanel | |||||
implicit none | implicit none | ||||
real, intent(in) :: v | real, intent(in) :: v | ||||
if (IsPortable) then | if (IsPortable) then | ||||
if(TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch == 0) then | |||||
if(TopDrivePanel%TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDrivePanel%TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch == 0) then | |||||
DrillingConsole%RTTorqueLimitKnob = 0 | DrillingConsole%RTTorqueLimitKnob = 0 | ||||
TopDrivePanel%TopDriveTorqueLimitKnob = v | TopDrivePanel%TopDriveTorqueLimitKnob = v | ||||
#ifdef deb | #ifdef deb | ||||
@@ -80,7 +80,7 @@ module CTopDrivePanel | |||||
call Log_3( 'TopDriveTorqueLimitKnob=', TopDrivePanel%TopDriveTorqueLimitKnob ) | call Log_3( 'TopDriveTorqueLimitKnob=', TopDrivePanel%TopDriveTorqueLimitKnob ) | ||||
#endif | #endif | ||||
endif | endif | ||||
if(TopDriveTdsPowerState == 0 .and. DrillingConsole%RTSwitch /= 0) then | |||||
if(TopDrivePanel%TopDriveTdsPowerState == 0 .and. DrillingConsole%RTSwitch /= 0) then | |||||
TopDrivePanel%TopDriveTorqueLimitKnob = 0 | TopDrivePanel%TopDriveTorqueLimitKnob = 0 | ||||
DrillingConsole%RTTorqueLimitKnob = real(ScaleRange(v, 0.0, 10.0, 0.0, 6000.0), 8) | DrillingConsole%RTTorqueLimitKnob = real(ScaleRange(v, 0.0, 10.0, 0.0, 6000.0), 8) | ||||
#ifdef deb | #ifdef deb | ||||
@@ -107,8 +107,8 @@ module CTopDrivePanel | |||||
implicit none | implicit none | ||||
real, intent(in) :: v | real, intent(in) :: v | ||||
if (IsPortable) then | if (IsPortable) then | ||||
if(TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch == 0) then | |||||
if(TopDrivePanel%TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDrivePanel%TopDriveTdsPowerState /= 0 .and. DrillingConsole%RTSwitch == 0) then | |||||
DrillingConsole%RTThrottle = 0 | DrillingConsole%RTThrottle = 0 | ||||
TopDrivePanel%RpmKnob = v | TopDrivePanel%RpmKnob = v | ||||
#ifdef deb | #ifdef deb | ||||
@@ -116,7 +116,7 @@ module CTopDrivePanel | |||||
call Log_3( 'RpmKnob=', TopDrivePanel%RpmKnob ) | call Log_3( 'RpmKnob=', TopDrivePanel%RpmKnob ) | ||||
#endif | #endif | ||||
endif | endif | ||||
if(TopDriveTdsPowerState == 0 .and. DrillingConsole%RTSwitch /= 0) then | |||||
if(TopDrivePanel%TopDriveTdsPowerState == 0 .and. DrillingConsole%RTSwitch /= 0) then | |||||
TopDrivePanel%RpmKnob = 0 | TopDrivePanel%RpmKnob = 0 | ||||
DrillingConsole%RTThrottle = real(ScaleRange(v, 0.0, 965.0, 0.0, 250.0), 8) | DrillingConsole%RTThrottle = real(ScaleRange(v, 0.0, 965.0, 0.0, 250.0), 8) | ||||
#ifdef deb | #ifdef deb | ||||
@@ -20,7 +20,7 @@ module CTopDrivePanelVariables | |||||
integer :: LED_BLINK = 2 | integer :: LED_BLINK = 2 | ||||
! Input vars | ! Input vars | ||||
! Type::TopDrivePanelType | |||||
Type::TopDrivePanelType | |||||
integer :: TopDriveTdsPowerState | integer :: TopDriveTdsPowerState | ||||
logical :: TopDriveTorqueWrench | logical :: TopDriveTorqueWrench | ||||
integer :: TopDriveDrillTorqueState | integer :: TopDriveDrillTorqueState | ||||
@@ -154,7 +154,7 @@ module COperationScenariosSettings | |||||
subroutine SetDefaultValues() | subroutine SetDefaultValues() | ||||
use COperationScenariosVariables | use COperationScenariosVariables | ||||
use CHoistingVariables, only: Hoisting%DriveType, TopDrive_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType | |||||
use CManifolds, only: RemoveSafetyValve_TripMode, RemoveSafetyValve_KellyMode | use CManifolds, only: RemoveSafetyValve_TripMode, RemoveSafetyValve_KellyMode | ||||
implicit none | implicit none | ||||
@@ -6,6 +6,7 @@ module CElevatorConnectionEnum | |||||
contains | contains | ||||
subroutine Evaluate_ElevatorConnection() | subroutine Evaluate_ElevatorConnection() | ||||
use CHoistingVariables | |||||
use CCommon, only: SetStandRack | use CCommon, only: SetStandRack | ||||
implicit none | implicit none | ||||
@@ -14,7 +14,7 @@ module CCloseSafetyValveLedNotificationVariables | |||||
subroutine Set_CloseSafetyValveLed(v) | subroutine Set_CloseSafetyValveLed(v) | ||||
! use CDrillingConsoleVariables, only: CloseSafetyValveLedHw => CloseSafetyValveLed | ! use CDrillingConsoleVariables, only: CloseSafetyValveLedHw => CloseSafetyValveLed | ||||
use CManifolds, only: CloseSafetyValve_TopDrive, CloseSafetyValve_KellyMode, CloseSafetyValve_TripMode | use CManifolds, only: CloseSafetyValve_TopDrive, CloseSafetyValve_KellyMode, CloseSafetyValve_TripMode | ||||
use CHoistingVariables, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
implicit none | implicit none | ||||
logical , intent(in) :: v | logical , intent(in) :: v | ||||
#ifdef ExcludeExtraChanges | #ifdef ExcludeExtraChanges | ||||
@@ -1,5 +1,6 @@ | |||||
module CIrIBopLedNotification | module CIrIBopLedNotification | ||||
use COperationScenariosVariables | use COperationScenariosVariables | ||||
! use CTopDrivePanelVariables | |||||
implicit none | implicit none | ||||
contains | contains | ||||
@@ -66,7 +67,7 @@ module CIrIBopLedNotification | |||||
!TOPDRIVE-CODE=60 | !TOPDRIVE-CODE=60 | ||||
if (Get_IrIbopPermission() .and.& | if (Get_IrIbopPermission() .and.& | ||||
Get_IrIBopLed() == .true. .and.& | Get_IrIBopLed() == .true. .and.& | ||||
TopDriveTdsPowerState == TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_OFF) then | |||||
call Set_IrIBopLed(.false.) | call Set_IrIBopLed(.false.) | ||||
return | return | ||||
@@ -21,7 +21,7 @@ module CIrSafetyValveLedNotificationVariables | |||||
RemoveSafetyValve_KellyMode, & | RemoveSafetyValve_KellyMode, & | ||||
RemoveSafetyValve_TripMode | RemoveSafetyValve_TripMode | ||||
use CSafetyValveEnumVariables, only: Set_SafetyValve_Install, Set_SafetyValve_Remove | use CSafetyValveEnumVariables, only: Set_SafetyValve_Install, Set_SafetyValve_Remove | ||||
use CHoistingVariables, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
implicit none | implicit none | ||||
logical , intent(in) :: v | logical , intent(in) :: v | ||||
#ifdef ExcludeExtraChanges | #ifdef ExcludeExtraChanges | ||||
@@ -12,9 +12,9 @@ module COpenSafetyValveLedNotificationVariables | |||||
contains | contains | ||||
subroutine Set_OpenSafetyValveLed(v) | subroutine Set_OpenSafetyValveLed(v) | ||||
! use CDrillingConsoleVariables, only: OpenSafetyValveLedHw => OpenSafetyValveLed | |||||
use CDrillingConsoleVariables!, only: OpenSafetyValveLedHw => OpenSafetyValveLed | |||||
use CManifolds, only: OpenSafetyValve_TopDrive, OpenSafetyValve_KellyMode, OpenSafetyValve_TripMode | use CManifolds, only: OpenSafetyValve_TopDrive, OpenSafetyValve_KellyMode, OpenSafetyValve_TripMode | ||||
use CHoistingVariables, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||||
implicit none | implicit none | ||||
logical , intent(in) :: v | logical , intent(in) :: v | ||||
#ifdef ExcludeExtraChanges | #ifdef ExcludeExtraChanges | ||||
@@ -18,7 +18,7 @@ module CTdsIbopLedNotification | |||||
!TOPDRIVE-CODE=61 | !TOPDRIVE-CODE=61 | ||||
if (Get_IbopLed() == .false. .and.& | if (Get_IbopLed() == .false. .and.& | ||||
TopDriveTdsPowerState == TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveIbop == .false.) then | TopDrivePanel%TopDriveIbop == .false.) then | ||||
call Set_IbopLed(.true.) | call Set_IbopLed(.true.) | ||||
@@ -31,7 +31,7 @@ module CTdsIbopLedNotification | |||||
!TOPDRIVE-CODE=62 | !TOPDRIVE-CODE=62 | ||||
if (Get_IbopLed() .and.& | if (Get_IbopLed() .and.& | ||||
TopDriveTdsPowerState == TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveIbop) then | TopDrivePanel%TopDriveIbop) then | ||||
call Set_IbopLed(.false.) | call Set_IbopLed(.false.) | ||||
@@ -12,7 +12,7 @@ module CTdsIbopLedNotificationVariables | |||||
contains | contains | ||||
subroutine Set_IbopLed(v) | subroutine Set_IbopLed(v) | ||||
use CTopDrivePanelVariables, only: TopDrivePanel%TopDriveIbopLed | |||||
use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveIbopLed | |||||
use CManifolds, Only: OpenTopDriveIBop, CloseTopDriveIBop | use CManifolds, Only: OpenTopDriveIBop, CloseTopDriveIBop | ||||
!use CLatchLedNotification | !use CLatchLedNotification | ||||
implicit none | implicit none | ||||
@@ -14,7 +14,7 @@ module CTdsPowerLedNotification | |||||
#endif | #endif | ||||
!TOPDRIVE-CODE=63 | !TOPDRIVE-CODE=63 | ||||
if (TopDriveTdsPowerState == TdsPower_OFF) then | |||||
if (TopDrivePanel%TopDriveTdsPowerState == TdsPower_OFF) then | |||||
call Set_PowerLed(.true.) | call Set_PowerLed(.true.) | ||||
return | return | ||||
end if | end if | ||||
@@ -12,7 +12,7 @@ module CTdsPowerLedNotificationVariables | |||||
contains | contains | ||||
subroutine Set_PowerLed(v) | subroutine Set_PowerLed(v) | ||||
use CTopDrivePanelVariables, only: TopDrivePanel%TopDriveTdsPowerLed | |||||
use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveTdsPowerLed | |||||
!use CLatchLedNotification | !use CLatchLedNotification | ||||
implicit none | implicit none | ||||
logical , intent(in) :: v | logical , intent(in) :: v | ||||
@@ -14,14 +14,14 @@ module CTdsTorqueWrenchLedNotification | |||||
!TOPDRIVE-CODE=81 | !TOPDRIVE-CODE=81 | ||||
if((Get_TdsBackupClamp() == BACKUP_CLAMP_OFF_BEGIN .or.& | if((Get_TdsBackupClamp() == BACKUP_CLAMP_OFF_BEGIN .or.& | ||||
Get_TdsBackupClamp() == BACKUP_CLAMP_FW_BEGIN) .and.& | Get_TdsBackupClamp() == BACKUP_CLAMP_FW_BEGIN) .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_TorqueWrenchLed(LED_BLINK) | call Set_TorqueWrenchLed(LED_BLINK) | ||||
return | return | ||||
endif | endif | ||||
!TOPDRIVE-CODE=81 | !TOPDRIVE-CODE=81 | ||||
if(Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | if(Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_TorqueWrenchLed(LED_ON) | call Set_TorqueWrenchLed(LED_ON) | ||||
return | return | ||||
endif | endif | ||||
@@ -12,7 +12,7 @@ module CTdsTorqueWrenchLedNotificationVariables | |||||
contains | contains | ||||
subroutine Set_TorqueWrenchLed(v) | subroutine Set_TorqueWrenchLed(v) | ||||
use CTopDrivePanelVariables, only: TopDrivePanel%TopDriveTorqueWrenchLed | |||||
use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveTorqueWrenchLed | |||||
implicit none | implicit none | ||||
integer , intent(in) :: v | integer , intent(in) :: v | ||||
@@ -1,5 +1,6 @@ | |||||
module CSwingDrillPermission | module CSwingDrillPermission | ||||
use COperationScenariosVariables | use COperationScenariosVariables | ||||
use CTopDrivePanelVariables | |||||
implicit none | implicit none | ||||
contains | contains | ||||
@@ -16,7 +17,7 @@ module CSwingDrillPermission | |||||
!TOPDRIVE-CODE=33 | !TOPDRIVE-CODE=33 | ||||
if (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | if (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | ||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | Get_TdsSwing() == TDS_SWING_OFF_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_SwingDrillPermission(.true.) | call Set_SwingDrillPermission(.true.) | ||||
return | return | ||||
@@ -20,7 +20,7 @@ module CSwingOffPermission | |||||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | ||||
Get_TdsSwing() == TDS_SWING_TILT_END .and.& | Get_TdsSwing() == TDS_SWING_TILT_END .and.& | ||||
Get_Slips() == SLIPS_SET_END .and.& | Get_Slips() == SLIPS_SET_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_SwingOffPermission(.true.) | call Set_SwingOffPermission(.true.) | ||||
return | return | ||||
@@ -33,7 +33,7 @@ module CSwingOffPermission | |||||
if (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | if (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | ||||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | ||||
Get_TdsSwing() == TDS_SWING_DRILL_END .and.& | Get_TdsSwing() == TDS_SWING_DRILL_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_SwingOffPermission(.true.) | call Set_SwingOffPermission(.true.) | ||||
return | return | ||||
@@ -18,7 +18,7 @@ module CSwingTiltPermission | |||||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | ||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | Get_TdsSwing() == TDS_SWING_OFF_END .and.& | ||||
Get_Slips() == SLIPS_SET_END .and.& | Get_Slips() == SLIPS_SET_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF) then | |||||
call Set_SwingTiltPermission(.true.) | call Set_SwingTiltPermission(.true.) | ||||
return | return | ||||
@@ -29,9 +29,9 @@ module CHookHeight | |||||
end function | end function | ||||
subroutine Subscribe_HookHeight() | subroutine Subscribe_HookHeight() | ||||
use CHookVariables, only: OnHookHeight => OnHookHeightChange | |||||
use CHookVariables!, only: OnHookHeight => OnHookHeightChange | |||||
implicit none | implicit none | ||||
call OnHookHeight%Add(Set_HookHeight) | |||||
call Hook%OnHookHeightChange%Add(Set_HookHeight) | |||||
end subroutine | end subroutine | ||||
end module CHookHeight | end module CHookHeight |
@@ -36,7 +36,7 @@ module COperationConditionEnum | |||||
! end subroutine | ! end subroutine | ||||
subroutine ButtonPress_Latch_OperationCondition() | subroutine ButtonPress_Latch_OperationCondition() | ||||
use CHoistingVariables, only: Hoisting%DriveType, Kelly_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, Kelly_DriveType | |||||
use CManifolds, only: InstallKellyCock | use CManifolds, only: InstallKellyCock | ||||
implicit none | implicit none | ||||
@@ -90,7 +90,7 @@ module COperationConditionEnum | |||||
end subroutine | end subroutine | ||||
subroutine ButtonPress_Unlatch_OperationCondition() | subroutine ButtonPress_Unlatch_OperationCondition() | ||||
use CHoistingVariables, only: Hoisting%DriveType, Kelly_DriveType | |||||
use CHoistingVariables!, only: Hoisting%DriveType, Kelly_DriveType | |||||
use CManifolds, only: RemoveKellyCock | use CManifolds, only: RemoveKellyCock | ||||
implicit none | implicit none | ||||
@@ -39,9 +39,6 @@ module COperationConditionEnumVariables | |||||
end function | end function | ||||
subroutine Set_OperationCondition_WN(v) | subroutine Set_OperationCondition_WN(v) | ||||
!DEC$ ATTRIBUTES DLLEXPORT :: Set_OperationCondition_WN | !DEC$ ATTRIBUTES DLLEXPORT :: Set_OperationCondition_WN | ||||
!DEC$ ATTRIBUTES ALIAS: 'Set_OperationCondition_WN' :: Set_OperationCondition_WN | !DEC$ ATTRIBUTES ALIAS: 'Set_OperationCondition_WN' :: Set_OperationCondition_WN | ||||
@@ -13,7 +13,7 @@ module CTdsBackupClamp | |||||
!TOPDRIVE-CODE=79 | !TOPDRIVE-CODE=79 | ||||
if(Get_TdsBackupClamp() == BACKUP_CLAMP_OFF_END .and.& | if(Get_TdsBackupClamp() == BACKUP_CLAMP_OFF_END .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTorqueWrench) then | TopDrivePanel%TopDriveTorqueWrench) then | ||||
call Set_TdsBackupClamp(BACKUP_CLAMP_FW_BEGIN) | call Set_TdsBackupClamp(BACKUP_CLAMP_FW_BEGIN) | ||||
@@ -23,7 +23,7 @@ module CTdsBackupClamp | |||||
!TOPDRIVE-CODE=80 | !TOPDRIVE-CODE=80 | ||||
if(Get_TdsBackupClamp() /= BACKUP_CLAMP_OFF_END .and.& | if(Get_TdsBackupClamp() /= BACKUP_CLAMP_OFF_END .and.& | ||||
Get_TdsBackupClamp() /= BACKUP_CLAMP_OFF_BEGIN .and.& | Get_TdsBackupClamp() /= BACKUP_CLAMP_OFF_BEGIN .and.& | ||||
TopDriveTdsPowerState /= TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState /= TdsPower_OFF .and.& | |||||
TopDrivePanel%TopDriveTorqueWrench == .false.) then | TopDrivePanel%TopDriveTorqueWrench == .false.) then | ||||
call Set_TdsBackupClamp(BACKUP_CLAMP_OFF_BEGIN) | call Set_TdsBackupClamp(BACKUP_CLAMP_OFF_BEGIN) | ||||
@@ -15,7 +15,7 @@ module CTdsSpineEnum | |||||
if (Get_TdsStemIn() .and.& | if (Get_TdsStemIn() .and.& | ||||
Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | Get_TdsConnectionModes() == TDS_CONNECTION_NOTHING .and.& | ||||
!Get_TdsConnectionPossible() .and.& | !Get_TdsConnectionPossible() .and.& | ||||
TopDriveTdsPowerState == TdsPower_FWD .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_FWD .and.& | |||||
TopDrivePanel%TopDriveDrillTorqueState == TdsMu_SPINE) then | TopDrivePanel%TopDriveDrillTorqueState == TdsMu_SPINE) then | ||||
call Set_TdsSpine(TDS_SPINE_CONNECT_BEGIN) | call Set_TdsSpine(TDS_SPINE_CONNECT_BEGIN) | ||||
@@ -26,7 +26,7 @@ module CTdsSpineEnum | |||||
if (Get_TdsStemIn() .and.& | if (Get_TdsStemIn() .and.& | ||||
Get_TdsTong() == TDS_TONG_BREAKOUT_END .and.& | Get_TdsTong() == TDS_TONG_BREAKOUT_END .and.& | ||||
Get_TdsConnectionModes() == TDS_CONNECTION_SPINE .and.& | Get_TdsConnectionModes() == TDS_CONNECTION_SPINE .and.& | ||||
TopDriveTdsPowerState == TdsPower_REV .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_REV .and.& | |||||
TopDrivePanel%TopDriveDrillTorqueState == TdsMu_SPINE) then | TopDrivePanel%TopDriveDrillTorqueState == TdsMu_SPINE) then | ||||
call Set_TdsSpine(TDS_SPINE_DISCONNECT_BEGIN) | call Set_TdsSpine(TDS_SPINE_DISCONNECT_BEGIN) | ||||
@@ -16,7 +16,7 @@ module CTdsTongEnum | |||||
!TOPDRIVE-CODE=1 | !TOPDRIVE-CODE=1 | ||||
if (Get_TdsConnectionModes() == TDS_CONNECTION_SPINE .and.& | if (Get_TdsConnectionModes() == TDS_CONNECTION_SPINE .and.& | ||||
Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | ||||
TopDriveTdsPowerState == TdsPower_FWD .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_FWD .and.& | |||||
TopDrivePanel%TopDriveDrillTorqueState == TdsMu_TORQ) then | TopDrivePanel%TopDriveDrillTorqueState == TdsMu_TORQ) then | ||||
call Set_TdsTong(TDS_TONG_MAKEUP_BEGIN) | call Set_TdsTong(TDS_TONG_MAKEUP_BEGIN) | ||||
@@ -29,7 +29,7 @@ module CTdsTongEnum | |||||
!TOPDRIVE-CODE=2 | !TOPDRIVE-CODE=2 | ||||
if (Get_TdsConnectionModes() == TDS_CONNECTION_STRING .and.& | if (Get_TdsConnectionModes() == TDS_CONNECTION_STRING .and.& | ||||
Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | Get_TdsBackupClamp() == BACKUP_CLAMP_FW_END .and.& | ||||
TopDriveTdsPowerState == TdsPower_REV .and.& | |||||
TopDrivePanel%TopDriveTdsPowerState == TdsPower_REV .and.& | |||||
TopDrivePanel%TopDriveDrillTorqueState == TdsMu_TORQ) then | TopDrivePanel%TopDriveDrillTorqueState == TdsMu_TORQ) then | ||||
call Set_TdsTong(TDS_TONG_BREAKOUT_BEGIN) | call Set_TdsTong(TDS_TONG_BREAKOUT_BEGIN) | ||||
@@ -630,7 +630,7 @@ module MudSystem | |||||
use CDrillWatchVariables | use CDrillWatchVariables | ||||
use CHOKEVARIABLES | use CHOKEVARIABLES | ||||
use CChokeManifoldVariables | use CChokeManifoldVariables | ||||
use CTanksVariables, TripTankVolume2 => Tank%TripTankVolume, TripTankDensity2 => Tank%TripTankDensity | |||||
use CTanksVariables | |||||
Use KickVariables | Use KickVariables | ||||
Use CHoistingVariables | Use CHoistingVariables | ||||
@@ -2640,8 +2640,8 @@ module MudSystem | |||||
!! TRIP TANK PANEL DISPLAY VALUES | !! TRIP TANK PANEL DISPLAY VALUES | ||||
!!====================================================================== | !!====================================================================== | ||||
TripTankVolume2= TripTankVolumeCalc/42. !(Drill Watch display) | |||||
TripTankDensity2= TripTankDensityCalc !(display) | |||||
Tank%TripTankVolume = TripTankVolumeCalc/42. !(Drill Watch display) | |||||
Tank%TripTankDensity= TripTankDensityCalc !(display) | |||||
IF (DataDisplayConsole%TripTankPowerSwitch==1 .and. IsPortable==.false.) THEN | IF (DataDisplayConsole%TripTankPowerSwitch==1 .and. IsPortable==.false.) THEN | ||||
@@ -13,7 +13,7 @@ subroutine TopDrive_MainSolver | |||||
!if ( (TopDriveTdsPowerState==-1) .and. (RpmKnob==0.) ) then !FWD | !if ( (TopDriveTdsPowerState==-1) .and. (RpmKnob==0.) ) then !FWD | ||||
if ( (TopDriveTdsPowerState==-1) .and. (IsStopped == .false.) ) then !FWD | |||||
if ( (TopDrivePanel%TopDriveTdsPowerState==-1) .and. (IsStopped == .false.) ) then !FWD | |||||
TDS%SoundBlower = .true. | TDS%SoundBlower = .true. | ||||
@@ -40,7 +40,7 @@ subroutine TopDrive_MainSolver | |||||
!else if ( (TopDriveTdsPowerState==1) .and. (RpmKnob==0.) ) then !REV | !else if ( (TopDriveTdsPowerState==1) .and. (RpmKnob==0.) ) then !REV | ||||
else if ( (TopDriveTdsPowerState==1) .and. (IsStopped == .false.) ) then !REV | |||||
else if ( (TopDrivePanel%TopDriveTdsPowerState==1) .and. (IsStopped == .false.) ) then !REV | |||||
TDS%SoundBlower = .true. | TDS%SoundBlower = .true. | ||||
@@ -68,7 +68,7 @@ subroutine TopDrive_MainSolver | |||||
else | else | ||||
if( (TopDriveTdsPowerState /= 0) .and. (IsStopped == .false.) ) then | |||||
if( (TopDrivePanel%TopDriveTdsPowerState /= 0) .and. (IsStopped == .false.) ) then | |||||
TDS%SoundBlower = .true. | TDS%SoundBlower = .true. | ||||
!Call SetSoundBlowerRT(TDS%SoundBlower) | !Call SetSoundBlowerRT(TDS%SoundBlower) | ||||
TopDrivePanel%TopDriveTdsPowerLed = 1 | TopDrivePanel%TopDriveTdsPowerLed = 1 | ||||
@@ -42,7 +42,7 @@ subroutine TopDrive_Solver | |||||
if ( TopDriveTdsPowerState==-1 .or. TDS_OldPowerMode==-1 ) then !FWD | |||||
if ( TopDrivePanel%TopDriveTdsPowerState==-1 .or. TDS_OldPowerMode==-1 ) then !FWD | |||||
if ( TopDrivePanel%TopDriveDrillTorqueState==0 .and. Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING ) then ! TdsMu_SPINE | if ( TopDrivePanel%TopDriveDrillTorqueState==0 .and. Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING ) then ! TdsMu_SPINE | ||||
TopDrivePanel%TopDriveOperationFaultLed = 0 | TopDrivePanel%TopDriveOperationFaultLed = 0 | ||||
@@ -162,7 +162,7 @@ subroutine TopDrive_Solver | |||||
TDS_OldPowerMode = -1 | TDS_OldPowerMode = -1 | ||||
end if | end if | ||||
else if ( TopDriveTdsPowerState==1 .or. TDS_OldPowerMode==1 ) then !REV | |||||
else if ( TopDrivePanel%TopDriveTdsPowerState==1 .or. TDS_OldPowerMode==1 ) then !REV | |||||
if ( TopDrivePanel%TopDriveDrillTorqueState==0 .and. Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING ) then ! TdsMu_SPINE | if ( TopDrivePanel%TopDriveDrillTorqueState==0 .and. Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING ) then ! TdsMu_SPINE | ||||
TopDrivePanel%TopDriveOperationFaultLed = 0 | TopDrivePanel%TopDriveOperationFaultLed = 0 | ||||
@@ -28,13 +28,13 @@ subroutine ROP_MainCalculation | |||||
!Real(8) :: Set_ROPGauge | !Real(8) :: Set_ROPGauge | ||||
zero_ROPcount = 0 | zero_ROPcount = 0 | ||||
No_of_Formations = FormationCount | |||||
No_of_Formations = Formation%Count | |||||
Drilling_verticalDepth = TD_WellTotalVerticalLength | Drilling_verticalDepth = TD_WellTotalVerticalLength | ||||
!===> MaximumWellDepthExceeded Warning | !===> MaximumWellDepthExceeded Warning | ||||
if ( Drilling_verticalDepth>=(Formation%Formations(FormationCount)%Top+Formation%Formations(FormationCount)%Thickness) ) then | |||||
if ( Drilling_verticalDepth>=(Formation%Formations(Formation%Count)%Top+Formation%Formations(Formation%Count)%Thickness) ) then | |||||
Rate_of_Penetration = 0.0d0 | Rate_of_Penetration = 0.0d0 | ||||
Call Set_ROP(Rate_of_Penetration) | Call Set_ROP(Rate_of_Penetration) | ||||
Call Activate_MaximumWellDepthExceeded() | Call Activate_MaximumWellDepthExceeded() | ||||
@@ -163,7 +163,7 @@ subroutine ROP_MainCalculation | |||||
Rate_of_Penetration = (f1*f2*f3*f4*f5*f6*f7*f8) ![ft/h] | Rate_of_Penetration = (f1*f2*f3*f4*f5*f6*f7*f8) ![ft/h] | ||||
Rate_of_Penetration = (DINT(Rate_of_Penetration*10.d0))/10.d0 | Rate_of_Penetration = (DINT(Rate_of_Penetration*10.d0))/10.d0 | ||||
if ( (TD_WellTotalLength==PathGeneration%Items(PathGenerationCount)%MeasuredDepth) ) then | |||||
if ( (TD_WellTotalLength==PathGeneration%Items(PathGeneration%ItemCount)%MeasuredDepth) ) then | |||||
Set_ROPGauge = Rate_of_Penetration | Set_ROPGauge = Rate_of_Penetration | ||||
Call Set_ROP(Set_ROPGauge) ![ft/h] | Call Set_ROP(Set_ROPGauge) ![ft/h] | ||||
Old_ROPValue(4) = Rate_of_Penetration | Old_ROPValue(4) = Rate_of_Penetration | ||||
@@ -30,7 +30,7 @@ subroutine Calculate_ROP | |||||
No_of_Formations = FormationCount !??????????????????????????????????????????? | |||||
No_of_Formations = Formation%Count !??????????????????????????????????????????? | |||||
Drilling_Depth = TD_WellTotalLength !????????????????????????? change to vertical depth of well | Drilling_Depth = TD_WellTotalLength !????????????????????????? change to vertical depth of well | ||||
@@ -168,6 +168,41 @@ | |||||
<File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsConnectionModesEnumVariables.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsConnectionModesEnumVariables.f90"/> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsElevatorModesEnum.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsElevatorModesEnum.f90"/> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsElevatorModesEnumVariables.f90"/></Filter> | <File RelativePath=".\CSharp\OperationScenarios\Enums\CTdsElevatorModesEnumVariables.f90"/></Filter> | ||||
<Filter Name="UnitySignals"> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CBucketEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CBucketEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CElevatorEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CElevatorEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowKellyDisconnectEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowKellyDisconnectEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowPipeDisconnectEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowPipeDisconnectEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CHeadEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CHeadEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CIbopEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CIbopEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CKellyEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CKellyEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CMouseHoleEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CMouseHoleEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\COperationConditionEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\COperationConditionEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSafetyValveEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSafetyValveEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSlipsEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSlipsEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSwingEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSwingEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsBackupClamp.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsBackupClampVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSpineEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSpineEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSwingEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSwingEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsTongEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsTongEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTongEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTongEnumVariables.f90"/></Filter> | |||||
<Filter Name="Notifications"> | <Filter Name="Notifications"> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Notifications\CCloseKellyCockLedNotification.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\Notifications\CCloseKellyCockLedNotification.f90"/> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Notifications\CCloseKellyCockLedNotificationVariables.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\Notifications\CCloseKellyCockLedNotificationVariables.f90"/> | ||||
@@ -233,47 +268,10 @@ | |||||
<Filter Name="SoftwareOutputs"> | <Filter Name="SoftwareOutputs"> | ||||
<File RelativePath=".\CSharp\OperationScenarios\SoftwareOutputs\CStringUpdate.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\SoftwareOutputs\CStringUpdate.f90"/> | ||||
<File RelativePath=".\CSharp\OperationScenarios\SoftwareOutputs\CStringUpdateVariables.f90"/></Filter> | <File RelativePath=".\CSharp\OperationScenarios\SoftwareOutputs\CStringUpdateVariables.f90"/></Filter> | ||||
<Filter Name="Test"> | |||||
<File RelativePath=".\CSharp\OperationScenarios\Test\TestOperationScenarios.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\Test\TestOperationScenariosVariables.f90"/></Filter> | |||||
<Filter Name="Test"/> | |||||
<Filter Name="Unity"> | <Filter Name="Unity"> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Unity\CUnityInputs.f90"/> | <File RelativePath=".\CSharp\OperationScenarios\Unity\CUnityInputs.f90"/> | ||||
<File RelativePath=".\CSharp\OperationScenarios\Unity\CUnityOutputs.f90"/></Filter> | |||||
<Filter Name="UnitySignals"> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CBucketEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CBucketEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CElevatorEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CElevatorEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowKellyDisconnectEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowKellyDisconnectEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowPipeDisconnectEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CFlowPipeDisconnectEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CHeadEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CHeadEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CIbopEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CIbopEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CKellyEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CKellyEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CMouseHoleEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CMouseHoleEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\COperationConditionEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\COperationConditionEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSafetyValveEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSafetyValveEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSlipsEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSlipsEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSwingEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CSwingEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsBackupClamp.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsBackupClampVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSpineEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSpineEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSwingEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsSwingEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsTongEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTdsTongEnumVariables.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTongEnum.f90"/> | |||||
<File RelativePath=".\CSharp\OperationScenarios\UnitySignals\CTongEnumVariables.f90"/></Filter></Filter> | |||||
<File RelativePath=".\CSharp\OperationScenarios\Unity\CUnityOutputs.f90"/></Filter></Filter> | |||||
<Filter Name="Problems"> | <Filter Name="Problems"> | ||||
<File RelativePath=".\CSharp\Problems\CBitProblems.f90"/> | <File RelativePath=".\CSharp\Problems\CBitProblems.f90"/> | ||||
<File RelativePath=".\CSharp\Problems\CBitProblemsVariables.f90"/> | <File RelativePath=".\CSharp\Problems\CBitProblemsVariables.f90"/> | ||||
@@ -9,7 +9,7 @@ subroutine TD_WellReadData | |||||
TD_WellIntervalsCount = PathGenerationCount + 1 ! +1 is belong to ROP hole | |||||
TD_WellIntervalsCount = PathGeneration%ItemCount + 1 ! +1 is belong to ROP hole | |||||
if (Allocated(TD_WellGeo)) deAllocate (TD_WellGeo) | if (Allocated(TD_WellGeo)) deAllocate (TD_WellGeo) | ||||
Allocate (TD_WellGeo(TD_WellIntervalsCount)) | Allocate (TD_WellGeo(TD_WellIntervalsCount)) | ||||
@@ -34,7 +34,7 @@ subroutine TD_StartUp | |||||
Rate_of_Penetration = 0.d0 | Rate_of_Penetration = 0.d0 | ||||
Bearing_Wear = 0.d0 | Bearing_Wear = 0.d0 | ||||
FormationNumber = 0 | FormationNumber = 0 | ||||
Old_ROPDepth = PathGeneration%Items(PathGenerationCount)%MeasuredDepth | |||||
Old_ROPDepth = PathGeneration%Items(PathGeneration%ItemCount)%MeasuredDepth | |||||
Old_ROPValue = 0.d0 | Old_ROPValue = 0.d0 | ||||
Set_ROPGauge = 0.d0 | Set_ROPGauge = 0.d0 | ||||