module CUnlatchLedNotification
    use OperationScenariosModule
    use CLog4
    implicit none
    contains
    
    subroutine Evaluate_UnlatchLed()
        use CCommon
        implicit none
        
        
        if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then
#ifdef OST
            print*, 'Evaluate_UnlatchLed=TopDrive'
#endif



            !TOPDRIVE-CODE=47
            if (Get_HookHeight() <= (TL() + NFC() - data%State%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.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                Get_ElevatorPickup() == .false. .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_UnlatchLed(.true.)
                return
            end if




            !TOPDRIVE-CODE=48
            if ((Get_HookHeight() >= (TL() + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + NFC()) .and. Get_HookHeight() <= (TL() + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + NFC() + data%State%OperationScenario%TG)) .and.& 
                GetStandRack() > 80 .and.&
                Get_JointConnectionPossible() == .false. .and.&
                (Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& 
                 Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_Slips() == SLIPS_SET_END) then
            
                call Set_UnlatchLed(.true.)
                return
            end if






            !TOPDRIVE-CODE=49
            if ((Get_HookHeight() >= TL() .and. Get_HookHeight() <= (TL() + NFC() + data%State%OperationScenario%SG)) .and.& 
                (Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& 
                 Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE) .and.&
                Get_TdsSwing() == TDS_SWING_TILT_END .and.&
                Get_FillMouseHoleLed() == .false.) then
            
                call Set_UnlatchLed(.true.)
                return
            end if








        endif
        
        
        
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then
#ifdef OST
            print*, 'Evaluate_UnlatchLed=Kelly'
#endif



            !OPERATION-CODE=40
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() - data%State%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.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                !Get_Elevator() == ELEVATOR_LATCH_STRING_END .and.&
                (Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.&
                !(Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.&
                !Get_LatchLed() == .false.
                Get_Swing() == SWING_WELL_END .and.& 
                Get_Slips() == SLIPS_SET_END ) then
            
                call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                return
            end if
            
            
            
            
            
            
            
            
            !OPERATION-CODE=41
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() >= (data%State%OperationScenario%HL + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (data%State%OperationScenario%HL + data%State%OperationScenario%SL - data%State%OperationScenario%ECG + Get_NearFloorConnection() + data%State%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.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                Get_StandRack() < 80 .and.&
                Get_JointConnectionPossible() == .false. .and.&
                !Get_Elevator() == ELEVATOR_UNLATCH_STAND_END .and.&
                !Get_LatchLed() == .false.
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.&
                Get_Swing() == SWING_WELL_END .and.& 
                Get_Slips() == SLIPS_SET_END) then
            
                call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                return
            end if
            
            
            
            
            
            !OPERATION-CODE=42
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() >= data%State%OperationScenario%HL .and. Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%SG) .and.&
                (Get_Elevator() /= ELEVATOR_LATCH_STRING_BEGIN .and.& 
                 Get_Elevator() /= ELEVATOR_UNLATCH_STRING_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_STAND_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_LATCH_SINGLE_BEGIN .and.&
                 Get_Elevator() /= ELEVATOR_UNLATCH_SINGLE_BEGIN) .and.&
                !Get_Elevator() == ELEVATOR_UNLATCH_SINGLE_END .and.&
                Get_Swing() == SWING_MOUSE_HOLE_END .and.& 
                !Get_LatchLed() == .false. .and.&
                Get_FillMouseHoleLed() == .false.) then
            
                call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                return
            end if
            
            
            
            
            
                !call Log_4('OPERATION-CODE=43-OPERATION_DRILL=', Get_OperationCondition() == OPERATION_DRILL)
                !call Log_4('OPERATION-CODE=43-Get_HookHeight=', Get_HookHeight() >= 27.41)
                !call Log_4('OPERATION-CODE=43-Get_Swing()=', Get_Swing() == SWING_RAT_HOLE_END)
                !call Log_4('OPERATION-CODE=43-Get_LatchLed()=', Get_LatchLed() == .false.)
            !OPERATION-CODE=43
            if (Get_OperationCondition() == OPERATION_DRILL .and.&
                Get_HookHeight() >= 27.41 .and.&
                !Get_LatchLed() == .false.
                Get_Swing() == SWING_RAT_HOLE_END) then
                !call Log_4('OPERATION-CODE=43-call Set_UnlatchLed(.true.)')
                call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                return
            end if
            
            
        
            call Set_UnlatchLed(.false.)

        endif
    end subroutine
    
    ! subroutine Subscribe_UnlatchLed()
    !     implicit none
        
    !     !**call data%State%unitySignals%OnOperationConditionChange%Add(Evaluate_UnlatchLed)
    !     ! call softwareInputs%OnHookHeightChange%Add(Evaluate_UnlatchLed)
    !     ! call softwareInputs%OnStandRackChanged%Add(Evaluate_UnlatchLed)
    !     call data%State%OperationScenario%OnElevatorConnectionChange%Add(Evaluate_UnlatchLed)
    !     !**call data%State%unitySignals%OnSwingChange%Add(Evaluate_UnlatchLed)
    !     !**call data%State%unitySignals%OnSlipsChange%Add(Evaluate_UnlatchLed)
    !     !**call data%State%notifications%OnLatchLedChange%Add(Evaluate_UnlatchLed)
    !     !**call data%State%notifications%OnFillMouseHoleLedChange%Add(Evaluate_UnlatchLed)
    ! end subroutine
    
end module CUnlatchLedNotification