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 data%Equipments%UnityInputs%OnJointConnectionPossibleChange%Add(Evaluate_TongNotification)
    !     call data%Equipments%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