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


            !TOPDRIVE-CODE=44
            if (Get_HookHeight() <= (TL() + NFC() - data%State%OperationScenario%ECG) .and.&
                Get_ElevatorConnectionPossible() .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_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_Slips() == SLIPS_SET_END) then
            
                call Set_LatchLed(.true.)
                return
            end if   


                
                
             
                
                
            !TOPDRIVE-CODE=45
            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() > 0 .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_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_Slips() == SLIPS_SET_END) then
            
                call Set_LatchLed(.true.)
                return
            end if    
                
                
                
                
                
                
            !TOPDRIVE-CODE=46
            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.&
                Get_ElevatorConnectionPossible() .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_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_TILT_END .and.&
                Get_FillMouseHoleLed()) then
            
                call Set_LatchLed(.true.)
                return
            end if     
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
        endif
        
        
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then
#ifdef OST
            print*, 'Evaluate_LatchLed=Kelly'
#endif

            !OPERATION-CODE=36
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() - data%State%OperationScenario%ECG) .and.&
                Get_ElevatorConnectionPossible() .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .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_STRING_END .and.&
                !Get_UnlatchLed() .and.&
                Get_Swing() == SWING_WELL_END .and.& 
                Get_Slips() == SLIPS_SET_END) then
            
                !call Log_4("OPERATION-CODE=36")
                call Set_LatchLed(.true.)
                !call Set_UnlatchLed(.false.)
                return
            end if 
            
            
            !OPERATION-CODE=37
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_StandRack() > 0 .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_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .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_STAND_END .and.&
                Get_ElevatorConnectionPossible() == .false. .and.&
                !Get_UnlatchLed() .and.&
                Get_Swing() == SWING_WELL_END .and.& 
                Get_Slips() == SLIPS_SET_END) then
            
                !call Log_4("OPERATION-CODE=37")
                call Set_LatchLed(.true.)
                !call Set_UnlatchLed(.false.)
                return
            end if
            
            
            
            
            
            
        
            
            
            
            
            
            
            !OPERATION-CODE=38 
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_ElevatorConnectionPossible() .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .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_UnlatchLed() .and.&
                Get_Swing() == SWING_MOUSE_HOLE_END .and.&
                Get_FillMouseHoleLed()) then
            
                !call Log_4("OPERATION-CODE=38")
                call Set_LatchLed(.true.)
                !call Set_UnlatchLed(.false.)
                return
            end if
            
            
            
            
            
            
            !OPERATION-CODE=39
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() >= 27.41 .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_UnlatchLed() .and.&
                Get_Swing() == SWING_RAT_HOLE_END) then
            
                !call Log_4("OPERATION-CODE=39")
                call Set_LatchLed(.true.)
                !call Set_UnlatchLed(.false.)
                return
            end if
            
        
            
            call Set_LatchLed(.false.)

        endif
        
        
        
        
        
            
            
    end subroutine
    
    ! subroutine Subscribe_LatchLed()
    !     use UnitySignalsModuleVariables
    !     use CStandRack
    !     use CUnityInputs, OnElevatorConnectionChangePosibility => OnElevatorConnectionPossibleChange
    !     use CSwingEnumVariables
    !     use CSlipsEnumVariables
    !     use CFillMouseHoleLedNotificationVariables
    !     implicit none
        
    !     call OnOperationConditionChange%Add(Evaluate_LatchLed)
    !     call OnStandRackChanged%Add(Evaluate_LatchLed)
    !     call OnElevatorConnectionChangePosibility%Add(Evaluate_LatchLed)
    !     call OnElevatorPickupChange%Add(Evaluate_LatchLed)
    !     call OnNearFloorPositionChange%Add(Evaluate_LatchLed)
    !     call OnSwingChange%Add(Evaluate_LatchLed)
    !     call OnSlipsChange%Add(Evaluate_LatchLed)
    !     call OnFillMouseHoleLedChange%Add(Evaluate_LatchLed)
        
        
    ! end subroutine
    
end module CLatchLedNotification