module CElevatorConnectionEnum
    use OperationScenariosModule
    use CLog3
    use CLog4
    implicit none
    contains
    
    subroutine Evaluate_ElevatorConnection()
        use CHoistingVariables
    use SimulationVariables
        use CCommon, only: SetStandRack
        implicit none
        
        
        if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then
#ifdef OST
            print*, 'Evaluate_ElevatorConnection=TopDrive'
#endif
        endif
        
        
        
        
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then
#ifdef OST
            print*, 'ElevatorConnection=Kelly'
#endif

            !!OPERATION-CODE=83
            !if (Get_OperationCondition() == OPERATION_TRIP .and.&
            !    Get_ElevatorConnection() == ELEVATOR_LATCH_STRING .and.&
            !    Get_ElevatorPickup() .and.&
            !    Get_Slips() ==  SLIPS_SET_END) then
            !    !call Log_4('OPERATION-CODE=83')
            !    call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING)
            !    return
            !end if
        







            

           
                
            !OPERATION-CODE=78
            if (Get_ElevatorPickup() == .false. .and.&
                Get_Tong() == TONG_BREAKOUT_END .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%PL) .and.&
                Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then
                call Set_ElevatorConnection(ELEVATOR_LATCH_SINGLE)
                return
            end if  
                
            !OPERATION-CODE=79
            if (Get_ElevatorPickup() == .false. .and.&
                Get_Tong() == TONG_BREAKOUT_END .and.&
                Get_HookHeight() >= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%SL - data%State%OperationScenario%LG) .and.&
                Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then
                call Set_ElevatorConnection(ELEVATOR_LATCH_STAND)
                return
            end if    

                
                
          !OPERATION-CODE=83
            if (Get_ElevatorPickup().and.&
                Get_ElevatorConnection() == ELEVATOR_LATCH_SINGLE) then
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE)
                return
            end if     
                
               
            !OPERATION-CODE=84
            if (Get_ElevatorPickup().and.&
                Get_ElevatorConnection() == ELEVATOR_LATCH_STAND) then
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND)
                return
            end if  










            !OPERATION-CODE=7
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !GetRotaryRpm() == 0.0d0 .and.&
                !Get_StandRack() > 0 .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                !Get_Swing() == SWING_WELL_END .and.&
                !Get_Slips() ==  SLIPS_SET_END .and.&
                !Get_LatchLed() .and.
                Get_Elevator() == ELEVATOR_LATCH_STAND_END) then
                !call Log_4('OPERATION-CODE=7')
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND)
                !call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                call SetStandRack(Get_StandRack() - 1)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                return
            end if
            
            !OPERATION-CODE=8
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.&
                !GetRotaryRpm() == 0.0d0 .and.&
                !Get_StandRack() < 80 .and.&
                !Get_ElevatorConnectionPossible() .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.&
                !Get_Swing() == SWING_WELL_END .and.&   
                !Get_Slips() ==  SLIPS_SET_END .and.&
                !Get_UnlatchLed() .and.&
                Get_Elevator() == ELEVATOR_UNLATCH_STAND_END) then
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING)
                !call Set_UnlatchLed(.false.)
                !call Set_LatchLed(.true.)
                call SetStandRack(Get_StandRack() + 1)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                !call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN)
                call Log_3('OPERATION-CODE=8')
                return
            end if
        
            !OPERATION-CODE=9
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !Get_HookHeight() >= 18.0 .and. Get_HookHeight() <= 22.0 .and.& 
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                !Get_Swing() == SWING_WELL_END .and.&   
                !Get_Slips() == SLIPS_SET_END .and.&
                !Get_LatchLed() .and.&
                !Get_ElevatorPickup() .and.&
                Get_Elevator() == ELEVATOR_LATCH_STRING_END) then
                !call Log_4('OPERATION-CODE=9')
                call Set_ElevatorConnection(ELEVATOR_LATCH_STRING)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                !call Set_UnlatchLed(.true.)
                !call Set_LatchLed(.false.)
                !call Set_UnlatchLed(.false.)
                !call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN)
                return
            end if
            
            !OPERATION-CODE=60
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& 
                Get_ElevatorPickup() == .false. .and.&
                Get_Slips() == SLIPS_SET_END .and.&
                !Get_Tong() /= TONG_MAKEUP_END .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING) then
                call Set_ElevatorConnection(ELEVATOR_LATCH_STRING)
                !call Set_Elevator(ELEVATOR_NEUTRAL)
                return
            end if
            
            !OPERATION-CODE=49
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_ElevatorPickup() .and.&
                Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING)
                return
            end if
            
            !OPERATION-CODE=10
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !GetRotaryRpm() == 0.0d0 .and.&
                (Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.&
                !Get_Swing() == SWING_WELL_END .and.&
                !Get_Slips() ==  SLIPS_SET_END .and.&
                !Get_UnlatchLed() .and.&
                Get_Elevator() == ELEVATOR_UNLATCH_STRING_END) then
                !call Log_4('OPERATION-CODE=10')
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                !call Set_UnlatchLed(.false.)
                !call Set_LatchLed(.true.)
                !call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN)
                return
            end if
            
            !OPERATION-CODE=11
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !Get_ElevatorConnectionPossible() .and.&
                Get_ElevatorPickup().and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                !Get_Swing() == SWING_MOUSE_HOLE_END .and.&
                !Get_LatchLed() .and.&
                !Get_FillMouseHoleLed() .and.&
                Get_Elevator() == ELEVATOR_LATCH_SINGLE_END) then
            
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE)
                !call Set_UnlatchLed(.true.)
                call Set_FillMouseHoleLed(.false.)
                call Set_MouseHole(MOUSE_HOLE_NEUTRAL)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                !call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN)
                return
            end if
            
            !OPERATION-CODE=12
            if (Get_OperationCondition() == OPERATION_TRIP .and.& 
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.&
                !Get_Swing() == SWING_MOUSE_HOLE_END .and.& 
                !Get_UnlatchLed() .and.&
                !Get_FillMouseHoleLed() == .false. .and.&
                Get_Elevator() == ELEVATOR_UNLATCH_SINGLE_END) then
                !call Log_4('OPERATION-CODE=12')
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING)
                !call Set_UnlatchLed(.false.)
                !call Set_LatchLed(.true.)
                call Set_FillMouseHoleLed(.true.)
                call Set_MouseHole(MOUSE_HOLE_NEUTRAL)
                call Set_Elevator(ELEVATOR_NEUTRAL)
                !call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN)
                return
            end if
        
            !OPERATION-CODE=13
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%PL) .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.&
                !Get_Swing() == SWING_WELL_END .and.&
                !Get_TongNotification() .and.&
                Get_ElevatorPickup().and.&
                Get_Tong() == TONG_BREAKOUT_END) then
                !call Log_4('OPERATION-CODE=13')
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE)
                call Set_StringUpdate(STRING_UPDATE_REMOVE_SINGLE)
                !call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE)
                call Set_Tong(TONG_NEUTRAL)
                return
            end if
        
            !OPERATION-CODE=14
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%PL) .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.&
                !Get_Swing() == SWING_WELL_END .and.&
                !Get_TongNotification() .and.&
                Get_ElevatorPickup().and.&
                Get_Tong() == TONG_MAKEUP_END) then
                !call Log_4('OPERATION-CODE=14')
                call Set_Tong(TONG_NEUTRAL)
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING)
                call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE)
                return
            end if

        
            !OPERATION-CODE=15
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() >= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%SL - data%State%OperationScenario%LG) .and.&
                !Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.&
                !Get_Swing() == SWING_WELL_END .and.& 
                !Get_TongNotification() .and.&
                Get_ElevatorPickup().and.&
                Get_Tong() == TONG_BREAKOUT_END) then
                call Set_Tong(TONG_NEUTRAL)
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND)
                call Set_StringUpdate(STRING_UPDATE_REMOVE_STAND)
                return
            end if
            
            !OPERATION-CODE=16 
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                !Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.&
                !Get_JointConnectionPossible() .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.&
                !Get_Swing() == SWING_WELL_END .and.&
                !Get_TongNotification() .and.&
                Get_ElevatorPickup().and.&
                Get_Tong() == TONG_MAKEUP_END) then
                !call Log_4('OPERATION-CODE=16')
                call Set_Tong(TONG_NEUTRAL)
                call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING)
                call Set_StringUpdate(STRING_UPDATE_ADD_STAND)
                return
            end if

                
                
                
                
             !OPERATION-CODE=75
            if (Get_ElevatorPickup() == .false. .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) then
                call Set_ElevatorConnection(ELEVATOR_LATCH_SINGLE)
                return
            end if
                
                
            !OPERATION-CODE=76
            if (Get_ElevatorPickup() == .false. .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND) then
                call Set_ElevatorConnection(ELEVATOR_LATCH_STAND)
                return
            end if  
                
            
                
                
            
                
        endif
        
        
            
    end subroutine
    
    ! subroutine Subscribe_ElevatorConnection()
    !     use CDrillingConsoleVariables
    ! use ConfigurationVariables
    ! use ConfigurationVariables
    !     implicit none
    !     call OnLatchPipePress%Add(ButtonPress_Latch_ElevatorConnection)
    !     call OnUnlatchPipePress%Add(ButtonPress_Unlatch_ElevatorConnection)
    !     call OnBreakoutLeverPress%Add(ButtonPress_Breakout_ElevatorConnection)
    !     call OnMakeupLeverPress%Add(ButtonPress_Makeup_ElevatorConnection)
    ! end subroutine
    
    subroutine ButtonPress_Latch_ElevatorConnection()
        use CCommon, only: SetStandRack
        implicit none
        
        
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then
#ifdef OST
            print*, 'ButtonPress_Latch_ElevatorConnection=TopDrive'
#endif




            !TOPDRIVE-CODE=73
            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_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_LatchLed()) then
                
                call Set_Elevator(ELEVATOR_LATCH_STAND_BEGIN)
                call Set_LatchLed(.false.)
                return
            end if

            
            
            
            
            
            
            !TOPDRIVE-CODE=74
            if (Get_HookHeight() <= (TL() + NFC() - data%State%OperationScenario%ECG) .and.& 
                GetRotaryRpm() == 0.0d0 .and.&
                Get_ElevatorConnectionPossible() .and.&
                Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_LatchLed()) then
                
                call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN)
                call Set_LatchLed(.false.)
                return
            end if
            
            
            
            
            
            
            
            !TOPDRIVE-CODE=75
            if (Get_ElevatorConnectionPossible() .and.&
                Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.&
                Get_TdsSwing() == TDS_SWING_TILT_END .and.&
                Get_LatchLed() .and.&
                Get_FillMouseHoleLed()) then
                
                call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN)
                call Set_LatchLed(.false.)
                return
            end if







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

            !OPERATION-CODE=86
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() - data%State%OperationScenario%ECG) .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                Get_LatchLed() .and.&
                GetRotaryRpm() == 0.0d0 .and.&
                Get_Swing() == SWING_WELL_END .and.&
                Get_ElevatorConnectionPossible() .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection()))  then
            
                !call Log_4("OPERATION-CODE=ELEVATOR_LATCH_STRING_BEGIN")            
                call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN)
                call Set_LatchLed(.false.)
                return
            endif
        
            !OPERATION-CODE=85
            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_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                Get_LatchLed() .and.&
                Get_Swing() == SWING_WELL_END)  then
                !Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL + RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG)
            
                call Set_Elevator(ELEVATOR_LATCH_STAND_BEGIN)
                call Set_LatchLed(.false.)
                return
            endif
            
            !OPERATION-CODE=87
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.&
                Get_LatchLed() .and.&
                Get_FillMouseHoleLed() .and.&
                Get_ElevatorConnectionPossible() .and.&
                Get_Swing() == SWING_MOUSE_HOLE_END)  then
            
                call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN)
                call Set_LatchLed(.false.)
                return
            endif


        endif
        
        
        
        
        
        
        
        
        
            
        
        
    end subroutine
    
    subroutine ButtonPress_Unlatch_ElevatorConnection()
        use CCommon, only: SetStandRack
        implicit none
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then
#ifdef OST
            print*, 'ButtonPress_Unlatch_ElevatorConnection=TopDrive'
#endif



            !TOPDRIVE-CODE=76
            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_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_UnlatchLed()) then
                
                call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            end if
            
            
            
            
            
            
            
            
            !TOPDRIVE-CODE=77
            if (Get_HookHeight() <= (TL() + NFC() - data%State%OperationScenario%ECG) .and.& 
                GetRotaryRpm() == 0.0d0 .and.&
                Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.&
                (Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING) .and.&
                Get_TdsSwing() == TDS_SWING_OFF_END .and.&
                Get_UnlatchLed()) then
                
                call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            end if
            
            
            
            
            
            
            
            !TOPDRIVE-CODE=78
            if ((Get_HookHeight() > TL() .and. Get_HookHeight() < (TL() + NFC() + data%State%OperationScenario%SG)) .and.& 
                Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE .and.&
                Get_TdsSwing() == TDS_SWING_TILT_END .and.&
                Get_UnlatchLed() .and.&
                Get_FillMouseHoleLed() == .false.) then
                
                call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            end if





        endif
        
        
        
        
        
        
        
        if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then
#ifdef OST
            print*, 'ButtonPress_Unlatch_ElevatorConnection=Kelly'
#endif
            !OPERATION-CODE=89
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() - data%State%OperationScenario%ECG) .and.&
                (Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.&
                Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection()) .and.& 
                Get_UnlatchLed() .and.&
                GetRotaryRpm() == 0.0d0 .and.&
                Get_Swing() == SWING_WELL_END .and.&
                Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0) then
                !Get_HookHeight() >= (HL + Get_NearFloorConnection() - 4.0) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() - 2.0))  then
            
                call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            endif
        
            !OPERATION-CODE=88
            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)
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.&
                Get_UnlatchLed() .and.&
                Get_Swing() == SWING_WELL_END)  then
            
                call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            endif
            
            !OPERATION-CODE=90
            if (Get_OperationCondition() == OPERATION_TRIP .and.&
                Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.&
                Get_UnlatchLed() .and.&
                Get_HookHeight() >= data%State%OperationScenario%HL  .and. Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%SG) .and.&
                !Get_JointConnectionPossible() .and.&
                Get_Swing() == SWING_MOUSE_HOLE_END)  then
            
                call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN)
                call Set_UnlatchLed(.false.)
                return
            endif

        endif
        
        
        
        
        
        
        
    end subroutine
    
    subroutine ButtonPress_Breakout_ElevatorConnection()
        implicit none
                
    end subroutine
    
    subroutine ButtonPress_Makeup_ElevatorConnection()
        implicit none
          
    end subroutine
    
end module CElevatorConnectionEnum