module COpenSafetyValveLedNotification
    use OperationScenariosModule
    implicit none
    contains
    
    subroutine Evaluate_OpenSafetyValveLed()
        implicit none
        
        
        
!        if (DriveType == TopDrive_DriveType) then
!#ifdef OST
!            print*, 'Evaluate_OpenSafetyValveLed=TopDrive'
!#endif
!        endif
!        
!        
!        
!        
!        
!        
!        
!        
!        if (DriveType == Kelly_DriveType) then
!#ifdef OST
!            print*, 'Evaluate_OpenSafetyValveLed=Kelly'
!#endif
!        endif
        
        
        
    end subroutine
    
    ! subroutine Subscribe_OpenSafetyValveLed()
    !     use CDrillingConsoleVariables
    ! use ConfigurationVariables
    ! use ConfigurationVariables
    !     implicit none
    !     call OnOpenSafetyValvePress%Add(ButtonPress_OpenSafetyValve)
    !     call OnOperationConditionChangeInt%Add(Set_Operation_OpenSafetyValveLed)
    ! end subroutine
    
    
    subroutine Set_Operation_OpenSafetyValveLed(v)
        implicit none
        integer , intent(in) :: v
#ifdef ExcludeExtraChanges
        if(data%State%notifications%operation_OpenSafetyValveLed == v) return
#endif
        data%State%notifications%operation_OpenSafetyValveLed = v
#ifdef deb
	    print*, 'data%State%notifications%operation_OpenSafetyValveLed=', data%State%notifications%operation_OpenSafetyValveLed
#endif
    end subroutine
    
    
    subroutine ButtonPress_OpenSafetyValve()
        implicit none
        
        
        if (data%State%Hoisting%DriveType == TopDrive_DriveType) then
#ifdef OST
            print*, 'ButtonPress_OpenSafetyValve=TopDrive'
#endif

            !TOPDRIVE-CODE=56
            if (Get_SafetyValveHeight() >= 3.0 .and. Get_SafetyValveHeight() <= 12.0 .and.&
                Get_OpenSafetyValveLed() == .false. .and.&
                Get_CloseSafetyValveLed()) then
                
                call Set_CloseSafetyValveLed(.false.)
                call Set_OpenSafetyValveLed(.true.)
                return
            end if

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

            !OPERATION-CODE=58
            if (Get_SafetyValveHeight() >= 3.0 .and. Get_SafetyValveHeight() <= 12.0 .and.&
                Get_OpenSafetyValveLed() == .false. .and.&
                Get_CloseSafetyValveLed()) then
                call Set_OpenSafetyValveLed(.true.)
                call Set_CloseSafetyValveLed(.false.)
                return
            end if


        endif
        
        
        
        
    end subroutine
    
end module COpenSafetyValveLedNotification