Compartir a través de


Detectar el tiempo de inactividad del usuario

En este tema se muestra cómo crear un procedimiento que se ejecutará si la aplicación de Access no detecta ninguna entrada de usuario durante un período de tiempo especificado. Implica la creación de un formulario oculto, DetectIdleTime, que realiza un seguimiento del tiempo de inactividad.

Siga estos pasos para crear el formulario DetectIdleTime.

  1. Cree un formulario en blanco que no esté basado en ninguna tabla o consulta y asígnele el nombre DetectIdleTime.

  2. Establezca las propiedades del formulario siguientes:

    Nota:

    El valor de TimerInterval indica, en milisegundos, la frecuencia con que la aplicación comprueba la inactividad del usuario. El valor 1000 equivale a 1 segundo.

    Propiedad Valor
    OnTimer [Procedimiento de evento]
    TimerInterval 1000
  3. Escriba el código siguiente para el procedimiento de evento de la propiedad OnTimer:

     Sub Form_Timer() 
             ' IDLEMINUTES determines how much idle time to wait for before 
             ' running the IdleTimeDetected subroutine. 
             Const IDLEMINUTES = 5 
    
             Static PrevControlName As String 
             Static PrevFormName As String 
             Static ExpiredTime 
    
             Dim ActiveFormName As String 
             Dim ActiveControlName As String 
             Dim ExpiredMinutes 
    
             On Error Resume Next 
    
             ' Get the active form and control name. 
    
             ActiveFormName = Screen.ActiveForm.Name 
             If Err Then 
                 ActiveFormName = "No Active Form" 
                 Err = 0 
             End If 
    
             ActiveControlName = Screen.ActiveControl.Name 
                 If Err Then 
                 ActiveControlName = "No Active Control" 
                 Err = 0 
             End If 
    
             ' Record the current active names and reset ExpiredTime if: 
             '    1. They have not been recorded yet (code is running 
             '       for the first time). 
             '    2. The previous names are different than the current ones 
             '       (the user has done something different during the timer 
             '        interval). 
             If (PrevControlName = "") Or (PrevFormName = "") _ 
               Or (ActiveFormName <> PrevFormName) _ 
               Or (ActiveControlName <> PrevControlName) Then 
                 PrevControlName = ActiveControlName 
                 PrevFormName = ActiveFormName 
                 ExpiredTime = 0 
             Else 
                 ' ...otherwise the user was idle during the time interval, so 
                 ' increment the total expired time. 
                 ExpiredTime = ExpiredTime + Me.TimerInterval 
             End If 
    
             ' Does the total expired time exceed the IDLEMINUTES? 
             ExpiredMinutes = (ExpiredTime / 1000) / 60 
             If ExpiredMinutes >= IDLEMINUTES Then 
                 ' ...if so, then reset the expired time to zero... 
                 ExpiredTime = 0 
                 ' ...and call the IdleTimeDetected subroutine. 
                 IdleTimeDetected ExpiredMinutes 
             End If 
           End Sub
    

A continuación, cree el procedimiento siguiente en el módulo de formulario:

 Sub IdleTimeDetected(ExpiredMinutes) 
         Dim Msg As String 
         Msg = "No user activity detected in the last " 
         Msg = Msg & ExpiredMinutes & " minute(s)!" 
         MsgBox Msg, 48 
       End Sub

Para ocultar el formulario DetectIdleTime mientras se abre, establezca el argumento WindowMode del método OpenForm en acHidden.

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.