|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287 |
- module CTongNotification
- use OperationScenariosModule
- implicit none
- contains
-
- subroutine Evaluate_TongNotification()
- implicit none
-
-
-
-
-
- if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then
- #ifdef OST
- print*, 'Evaluate_TongNotification=TopDrive'
- #endif
-
-
-
-
- !TOPDRIVE-CODE=50
- if (((Get_HookHeight() >= (TL() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + NFC() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (TL() + NFC() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + data%State%OperationScenario%TG)) .or.&
- (Get_HookHeight() >= (TL() + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + NFC() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (TL() + NFC() + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + data%State%OperationScenario%TG))).and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.&
- ((Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .or.&
- Get_Tong() == TONG_NEUTRAL ) .and.&
- (Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING) .and.&
- Get_TdsSwing() == TDS_SWING_OFF_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
- !TOPDRIVE-CODE=51
- if (GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- (Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_SINGLE .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE) .and.&
- Get_TdsSwing() == TDS_SWING_OFF_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
-
-
-
- !TOPDRIVE-CODE=52
- if (GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- (Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STAND .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND) .and.&
- Get_TdsSwing() == TDS_SWING_OFF_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
- endif
-
-
-
-
-
-
-
-
-
-
- if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then
- #ifdef OST
- print*, 'Evaluate_TongNotification=Kelly'
- #endif
-
- !OPERATION-CODE=44
- 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() >= (data%State%OperationScenario%HKL + Get_NearFloorConnection() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (data%State%OperationScenario%HKL + Get_NearFloorConnection() + data%State%OperationScenario%TG)) .or.&
- (Get_HookHeight() >= (data%State%OperationScenario%HKL + Get_NearFloorConnection() + data%State%OperationScenario%PL -data%State%OperationScenario%RE) .and. Get_HookHeight() <= (data%State%OperationScenario%HKL + Get_NearFloorConnection() + data%State%OperationScenario%TG + data%State%OperationScenario%PL))).and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_KellyConnection() == KELLY_CONNECTION_STRING .and.&
- Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.&
- Get_Swing() == SWING_WELL_END .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
- !OPERATION-CODE=45
- if (Get_OperationCondition() == OPERATION_DRILL .and.&
- Get_HookHeight() >= 66 .and. Get_HookHeight() <= 69 .and.&
- Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_MOUSE_HOLE_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
- !OPERATION-CODE=46
- if (Get_OperationCondition() == OPERATION_DRILL .and.&
- Get_JointConnectionPossible() .and.&
- Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_MOUSE_HOLE_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
- !OPERATION-CODE=47
- if (Get_OperationCondition() == OPERATION_DRILL .and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_WELL_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
- !OPERATION-CODE=48
- if (Get_OperationCondition() == OPERATION_DRILL .and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_WELL_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- !OPERATION-CODE=50
- if (Get_OperationCondition() == OPERATION_TRIP .and.&
- ((Get_HookHeight() >= (data%State%OperationScenario%HL + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + Get_NearFloorConnection() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + data%State%OperationScenario%TG)) .or.&
- (Get_HookHeight() >= (data%State%OperationScenario%HL + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + Get_NearFloorConnection() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%TG - data%State%OperationScenario%ECG + data%State%OperationScenario%SL))).and.&
- Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_WELL_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
- !OPERATION-CODE=51
- if (Get_OperationCondition() == OPERATION_TRIP .and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_WELL_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
-
- !OPERATION-CODE=52
- if (Get_OperationCondition() == OPERATION_TRIP .and.&
- GetRotaryRpm() == 0.0d0 .and.&
- Get_JointConnectionPossible() .and.&
- Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.&
- (Get_Tong() /= TONG_BREAKOUT_BEGIN .and.&
- Get_Tong() /= TONG_MAKEUP_BEGIN) .and.&
- Get_Swing() == SWING_WELL_END .and.&
- Get_Slips() == SLIPS_SET_END) then
-
- call Set_TongNotification(.true.)
- return
- end if
-
-
-
-
- !if (Get_OperationCondition() == OPERATION_DRILL .and.&
- ! Get_KellyConnection() == KELLY_CONNECTION_STRING .and.&
- ! Get_Swing() == SWING_WELL_END .and.&
- ! Get_Slips() == SLIPS_SET_END) then
- !
- ! call Set_TongNotification(.true.)
- ! return
- !end if
- !
-
-
- call Set_TongNotification(.false.)
-
- endif
-
-
-
-
-
-
-
-
-
-
- end subroutine
-
- ! subroutine Subscribe_TongNotification()
- ! implicit none
-
- ! call data%State%unitySignals%OnOperationConditionChange%Add(Evaluate_TongNotification)
- ! ! call softwareInputs%OnHookHeightChange%Add(Evaluate_TongNotification)
- ! call UnityInputs%OnJointConnectionPossibleChange%Add(Evaluate_TongNotification)
- ! call UnityInputs%OnSingleSetInMouseHoleChange%Add(Evaluate_TongNotification)
- ! call data%State%OperationScenario%OnElevatorConnectionChange%Add(Evaluate_TongNotification)
- ! call KellyConnectionEnum%OnKellyConnectionChange%Add(Evaluate_TongNotification)
- ! call data%State%unitySignals%OnSwingChange%Add(Evaluate_TongNotification)
- ! call data%State%unitySignals%OnSlipsChange%Add(Evaluate_TongNotification)
-
- ! end subroutine
-
-
-
- end module CTongNotification
|