module COperationScenariosMain
    use CIActionReference
    implicit none
    public
    ! procedure (ActionVoid), pointer :: UpdateUnityPtr
    contains
        
    subroutine OperationScenarios_Step
        ! use CSimulationVariables
        use OperationScenariosModule
        use CElevatorConnectionEnum
        use CCloseKellyCockLedNotification
        use CCloseSafetyValveLedNotification
        use CFillMouseHoleLedNotification
        use CIrIBopLedNotification
        use CIrSafetyValveLedNotification
        use CLatchLedNotification
        use COpenKellyCockLedNotification        
        use COpenSafetyValveLedNotification
        use CSlipsNotification
        use CSwingLedNotification
        use CTongNotification
        use CUnlatchLedNotification
        use CInstallFillupHeadPermission
        use CInstallMudBucketPermission
        use CIrIbopPermission
        use CIrSafetyValvePermission
        use CRemoveFillupHeadPermission
        use CRemoveMudBucketPermission
        use SoftwareInputsVariables
        ! use CHookHeight
        ! use CIbopHeight
        ! use CNearFloorConnection
        ! use CSafetyValveHeight
        ! use CSlackOff
        ! use CStandRack
        ! use CStringPressure
        ! use CZeroStringSpeed
        use CUnityInputs, only: &
            Get_ElevatorConnectionPossible, &
            Get_JointConnectionPossible, &
            Get_ElevatorPickup, &
            Get_NearFloorPosition, &
            Get_SingleSetInMouseHole
        ! use CBucketEnum
        ! use UnitySignalsModule
        use CElevatorEnum
        ! use CHeadEnum
        use CIbopEnum
        use CKellyEnum
        use CMouseHoleEnum
        use UnitySignalsModule
        use CSafetyValveEnum
        use CSlipsEnum
        use CSwingEnum
        use CTongEnum
        ! use CStringUpdate
        use CFlowPipeDisconnectEnum
        use CFlowKellyDisconnectEnum
        use CFillupHeadPermission
        use CSwingDrillPermission
        use CSwingOffPermission
        use CSwingTiltPermission
        ! use CTdsStemJointHeight
        ! use UnitySignalsModule !for CTdsConnectionModesEnum
        use CTdsElevatorModesEnum
        use CTdsSpineEnum
        use CTdsSwingEnum
        use CTdsTongEnum
        use CTdsBackupClamp
        use CTdsIbopLedNotification
        use CTdsPowerLedNotification
        use CTdsTorqueWrenchLedNotification

        implicit none

        call Evaluate_KellyConnection()
        call Evaluate_ElevatorConnection()
            
        call Evaluate_CloseKellyCockLed()
        call Evaluate_CloseSafetyValveLed()
        call Evaluate_FillMouseHoleLed()
        call Evaluate_IrIBopLed()
        call Evaluate_IrSafetyValveLed()
        call Evaluate_LatchLed()
        call Evaluate_OpenKellyCockLed()
        call Evaluate_OpenSafetyValveLed()
        call Evaluate_SlipsNotification()
        call Evaluate_SwingLed()
        call Evaluate_TongNotification()
        call Evaluate_UnlatchLed()
            
        call Evaluate_InstallFillupHeadPermission()
        call Evaluate_InstallMudBucketPermission()
        call Evaluate_IrIbopPermission()
        call Evaluate_IrSafetyValvePermission()
        call Evaluate_RemoveFillupHeadPermission()
        call Evaluate_RemoveMudBucketPermission()
            
        call Evaluate_MudBucket()
        call Evaluate_Elevator()
        call Evaluate_FillupHead()
        call Evaluate_Ibop()
        call Evaluate_Kelly()
        call Evaluate_MouseHole()
        call Evaluate_MouseHole()
        call Evaluate_OperationCondition()
        call Evaluate_SafetyValve()
        call Evaluate_Slips()
        call Evaluate_Swing()
        call Evaluate_Tong()
            
        ! call Evaluate_StringUpdate()
            
        call Evaluate_FlowKellyDisconnect()
        call Evaluate_FlowPipeDisconnect()
            
        !if(Get_FillMouseHoleLed()) then
        !    call Set_MouseHole(MOUSE_HOLE_FILL)
        !else 
        !    if((Get_KellyConnection()  == KELLY_CONNECTION_SINGLE .or.&
        !        Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) .and.&
        !        Get_HookHeight() >= 95.0 ) then
        !        call Set_MouseHole(MOUSE_HOLE_NEUTRAL)
        !    else
        !        call Set_MouseHole(MOUSE_HOLE_EMPTY)
        !    endif
        !endif
            
            
            
            
            
            
            
            
        !topdrive
        call Evaluate_TdsElevatorModes()
        call Evaluate_TdsConnectionModes()
        call Evaluate_SwingTiltPermission()
        call Evaluate_SwingOffPermission()
        call Evaluate_SwingDrillPermission()
        call Evaluate_FillupHeadPermission()
        call Evaluate_TdsTong()
        call Evaluate_TdsBackupClamp()
        call Evaluate_TdsSwing()
        call Evaluate_TdsSpine()
            
        call Evaluate_PowerLed()
        call Evaluate_IbopLed()
           
        call Evaluate_TorqueWrenchLed()

    end subroutine OperationScenarios_Step
        
    ! subroutine UpdateUnity()
    !     implicit none
    !     if(associated(UpdateUnityPtr)) call UpdateUnityPtr()
    ! end subroutine    
    
    subroutine Kelly_ConnectionNothing
        ! use CSwingEnumVariables
        ! use CSlipsEnumVariables
        use UnitySignalVariables
    use UnitySignalsModule
        use CHook
    use SimulationVariables
        implicit none
        
        call Set_HookHeight(75.0)
        call sleep(1)
        
        ! first wait for unity to get to starting point
        loop1: do
            if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1
            call sleepqq(100)
        enddo loop1
        call sleep(1)
        
        !TODO: possibly goto a position to activate swing
        
        ! goto preferred swing position
        if(data%State%unitySignals%Swing_S == SWING_MOUSE_HOLE_END) then
            call Set_Swing(SWING_MOUSE_HOLE_BEGIN)
            !@call UpdateUnity()
            loop2: do
                if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2
                call sleepqq(100)
            enddo loop2
        elseif (data%State%unitySignals%Swing_S == SWING_RAT_HOLE_END) then
            call Set_Swing(SWING_RAT_HOLE_BEGIN)
            !@call UpdateUnity()
            loop3: do
                if(Get_Swing() == SWING_RAT_HOLE_END) exit loop3
                call sleepqq(100)
            enddo loop3
        !elseif (Swing_S == SWING_WELL_END) then
        !    call Set_Swing(SWING_WELL_BEGIN)
        !    !@call UpdateUnity()
        !    loop4: do
        !        if(Get_Swing() == SWING_WELL_END) exit loop4
        !        call sleepqq(100)
        !    enddo loop4
        endif
        call sleep(3)
        
        ! move to final hook height
        call Update_HookHeight_From_Snapshot()
        call sleep(3)
        
    end subroutine Kelly_ConnectionNothing
    
    
    
    
    
    subroutine Kelly_ConnectionString
        ! use CSwingEnumVariables
        ! use CSlipsEnumVariables
        use UnitySignalVariables
    use UnitySignalsModule
        use CHook
    use SimulationVariables
        ! use CTongEnumVariables
        implicit none
        
        call Set_HookHeight(75.0)
        call sleep(1)
        
        ! first wait for unity to get to starting point
        loop1: do
            if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1
            call sleepqq(100)
        enddo loop1
        call sleep(1)
        
        ! goto connection to string position
        call Set_HookHeight_S(66.7)
        call sleep(1)
        
        ! start tong makeup
        call Set_Tong(TONG_MAKEUP_BEGIN)
        !@call UpdateUnity()
        loop2: do
            if(Get_Tong() == TONG_MAKEUP_END) exit loop2
            call sleepqq(100)
        enddo loop2
        call sleepqq(100)
        
        ! release slips
        call Set_Slips(SLIPS_UNSET_BEGIN)
        !@call UpdateUnity()
        loop3: do
            if(Get_Slips() == SLIPS_UNSET_END) exit loop3
            call sleepqq(100)
        enddo loop3
        call sleepqq(100)
        
        ! move to final hook height
        call Update_HookHeight_From_Snapshot()
        call sleep(3)
        
        
        ! put slips to saved position
        if(data%State%unitySignals%Slips_S == SLIPS_SET_END) then
            
            call Set_Slips(SLIPS_SET_BEGIN)
            !@call UpdateUnity()
            loop4: do
                if(Get_Slips() == SLIPS_SET_END) exit loop4
                call sleepqq(100)
            enddo loop4
            call sleep(1)
        endif
        
        
    end subroutine Kelly_ConnectionString
    
    
    
    
    subroutine Kelly_ConnectionSingle
        ! use CSwingEnumVariables
        ! use CSlipsEnumVariables
        ! use CTongEnumVariables
        use UnitySignalVariables
    use UnitySignalsModule
        use CHook
    use SimulationVariables
        implicit none
        
        call Set_HookHeight(75.0)
        call sleep(1)
        
        ! first wait for unity to get to starting point
        loop1: do
            if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1
            call sleepqq(100)
        enddo loop1
        call sleep(1)
        
        
        ! goto swing mouse hole position
        call Set_HookHeight_S(70.0)
        call sleep(1)
        
        ! swing mouse hole
        call Set_Swing(SWING_MOUSE_HOLE_BEGIN)
        !@call UpdateUnity()
        loop2: do
            if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2
            call sleepqq(100)
        enddo loop2
        call sleepqq(100)
        
        
        ! goto makeup pipe location
        call Set_HookHeight_S(65.0)
        call sleep(1)
        
        
        ! start tong makeup
        call Set_Tong(TONG_MAKEUP_BEGIN)
        !@call UpdateUnity()
        loop3: do
            if(Get_Tong() == TONG_MAKEUP_END) exit loop3
            call sleepqq(100)
        enddo loop3
        call sleepqq(100)
        
        
        
        if (data%State%unitySignals%Swing_S == SWING_WELL_END) then ! already in mouse hole
            
            ! goto swing location
            call Set_HookHeight_S(98.0)
            call sleep(1)
            
            ! goto preferred swing position
            call Set_Swing(SWING_WELL_BEGIN)
            !@call UpdateUnity()
            loop4: do
                if(Get_Swing() == SWING_WELL_END) exit loop4
                call sleepqq(100)
            enddo loop4
            call sleep(2)
            
        endif
        
        
        ! move to final hook height
        call Update_HookHeight_From_Snapshot()
        call sleep(3)
        
    end subroutine Kelly_ConnectionSingle
        
    subroutine Elevator_ConnectionNothing
        ! use CSwingEnumVariables
        ! use CSlipsEnumVariables
        use UnitySignalVariables
    use UnitySignalsModule
        use CHook
    use SimulationVariables
        ! use CKellyEnumVariables
        implicit none
        
        call Set_HookHeight(75.0)
        call sleep(1)
        
        ! first wait for unity to get to starting point
        loop1: do
            if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1
            call sleepqq(100)
        enddo loop1
        call sleep(1)
        
        
        !TODO: possibly goto a position to activate swing
        
        !! first goto mouse hole
        !call Set_Swing(SWING_MOUSE_HOLE_BEGIN)
        !!@call UpdateUnity()
        !loop2: do
        !    if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2
        !    call sleepqq(100)
        !enddo loop2
        !call sleep(1)
        !
        !! then goto rat hole
        !call Set_Swing(SWING_RAT_HOLE_BEGIN)
        !!@call UpdateUnity()
        !loop3: do
        !    if(Get_Swing() == SWING_RAT_HOLE_END) exit loop3
        !    call sleepqq(100)
        !enddo loop3
        !call sleep(1)
        
        ! kelly back
        call Set_Kelly(KELLY_REMOVE)
        call sleepqq(100)
        
        ! goto preferred swing position
        if(data%State%unitySignals%Swing_S == SWING_MOUSE_HOLE_END) then
            call Set_Swing(SWING_MOUSE_HOLE_BEGIN)
            !@call UpdateUnity()
            loop4: do
                if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop4
                call sleepqq(100)
            enddo loop4
        elseif (data%State%unitySignals%Swing_S == SWING_RAT_HOLE_END) then
            call Set_Swing(SWING_RAT_HOLE_BEGIN)
            !@call UpdateUnity()
            loop5: do
                if(Get_Swing() == SWING_RAT_HOLE_END) exit loop5
                call sleepqq(100)
            enddo loop5
        elseif (data%State%unitySignals%Swing_S == SWING_WELL_END) then
            call Set_Swing(SWING_WELL_BEGIN)
            !@call UpdateUnity()
            loop6: do
                if(Get_Swing() == SWING_WELL_END) exit loop6
                call sleepqq(100)
            enddo loop6
        endif
        call sleepqq(100)
        
        
        
        ! move to final hook height
        call Update_HookHeight_From_Snapshot()
        call sleep(3)
        
    end subroutine Elevator_ConnectionNothing
    
    
    
    
    
    subroutine Elevator_ConnectionString
        implicit none
    end subroutine Elevator_ConnectionString
    
    
    
    
    
    
    
    subroutine Elevator_ConnectionStand
        implicit none
    end subroutine Elevator_ConnectionStand
    
    
    
    
    
    
    subroutine Elevator_ConnectionSingle
        implicit none
    end subroutine Elevator_ConnectionSingle

end module COperationScenariosMain