Forum |  HardWare.fr | News | Articles | PC | S'identifier | S'inscrire | Shop Recherche
890 connectés 

  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  Activation clavier touche Verr.num

 


 Mot :   Pseudo :  
 
Bas de page
Auteur Sujet :

Activation clavier touche Verr.num

n°1777222
mnyware
En vrai YATA !!!
Posté le 25-08-2008 à 15:08:20  profilanswer
 

Salut à tous  
 
Je veux qu'au démarrage d'une de mes applications les touches caps lock et num lock soit activés
 
j'ai trouvé un source permettant de le faire
 
ce qui ne marche pas :
les voyants des touches ne sont pas allumés
pour les touches majuscules ça marche mais pas le pavé numérique
 

Code :
  1. //Module
  2. Private Type KeyboardBytes
  3. kbByte(0 To 255) As Byte
  4. End Type
  5. Private Declare Function GetKeyboardState Lib "user32" (kbArray As KeyboardBytes) As Long
  6. Private Declare Function SetKeyboardState Lib "user32" (kbArray As KeyboardBytes) As Long
  7. Dim kbArray As KeyboardBytes, kbOld As KeyboardBytes
  8. Sub Active(vkKey As Long, Actif As Byte)
  9.      GetKeyboardState kbArray
  10.      kbArray.kbByte(vkKey) = Actif
  11.      SetKeyboardState kbArray
  12. End Sub
  13. //dans mon formulaire
  14. Active vbKeyCapital, 1
  15. Active vbKeyNumlock, 1


 
vous avez une autre solution ou des astuces ...
merci bien

mood
Publicité
Posté le 25-08-2008 à 15:08:20  profilanswer
 

n°1777227
kiki29
Posté le 25-08-2008 à 15:16:28  profilanswer
 

Salut,à adapter à ton contexte  
Insérer dans un module de Classe


Option Explicit
 
Private Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As _
                                                                 Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Private Declare Function SetKeyboardState Lib "user32" (lppbKeyState As Byte) _
                                          As Long
Private Declare Function GetKeyState Lib "user32" (ByVal nVirtKey As Long) As _
                                     Integer
Private Declare Function MapVirtualKey Lib "user32" Alias "MapVirtualKeyA" _
                                       (ByVal wCode As Long, ByVal wMapType As Long) As Long
 
Public Const VK_NUMLOCK = &H90
Public Const VK_SCROLL = &H91
Public Const VK_CAPITAL = &H14
Private Const KEYEVENTF_EXTENDEDKEY = &H1
Private Const KEYEVENTF_KEYUP = &H2
 
Public Sub SetKeyState(ByVal Key As Long, ByVal State As Boolean)
 
    keybd_event Key, MapVirtualKey(Key, 0), KEYEVENTF_EXTENDEDKEY Or 0, 0
    keybd_event Key, MapVirtualKey(Key, 0), KEYEVENTF_EXTENDEDKEY Or KEYEVENTF_KEYUP, 0
    If Key = 20 And State = False Then
        keybd_event 16, 0, 0, 0
        keybd_event 16, 0, 2, 0
    End If
 
End Sub
 
Public Property Get CapsLock() As Boolean
    CapsLock = GetKeyState(VK_CAPITAL) = 1
End Property
 
Public Property Let CapsLock(ByVal Value As Boolean)
    SetKeyState VK_CAPITAL, Value
End Property
 
Public Property Get NumLock() As Boolean
    NumLock = GetKeyState(VK_NUMLOCK) = 1
End Property
 
Public Property Let NumLock(ByVal Value As Boolean)
    SetKeyState VK_NUMLOCK, Value
End Property
 
Public Property Get ScrollLock() As Boolean
    ScrollLock = GetKeyState(VK_SCROLL) = 1
End Property
 
Public Property Let ScrollLock(ByVal Value As Boolean)
    SetKeyState VK_SCROLL, Value
End Property


 
Dans un Module standard


Option Explicit
 
Sub Bouton1_QuandClic()
    If NumLock = False Then NumLock = True
End Sub
 
Sub Bouton2_QuandClic()
    If NumLock = True Then NumLock = False
End Sub

n°1777232
mnyware
En vrai YATA !!!
Posté le 25-08-2008 à 15:19:02  profilanswer
 

j'essaye toute de suite  
merci

n°1777241
kiki29
Posté le 25-08-2008 à 15:23:27  profilanswer
 

re,dans ton contexte dans module ThisWorkBook


Option Explicit
 
Private Sub Workbook_Open()
    If NumLock = False Then NumLock = True
    If CapsLock = False Then CapsLock = True
End Sub


Message édité par kiki29 le 25-08-2008 à 15:24:24
n°1777257
mnyware
En vrai YATA !!!
Posté le 25-08-2008 à 15:34:50  profilanswer
 

ça marche très bien  :D
 
merci kiki29 ;)

n°1971608
hookiller
Posté le 06-03-2010 à 15:52:58  profilanswer
 

est il possible d'avoire se prog en VBScript

n°1971620
kiki29
Posté le 06-03-2010 à 17:57:46  profilanswer
 

Salut,qqch comme ceci, à toi de poursuivre


set WshShell = CreateObject("WScript.Shell" )  
WshShell.SendKeys "{NUMLOCK}"


Message édité par kiki29 le 06-03-2010 à 17:58:00

Aller à :
Ajouter une réponse
  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  Activation clavier touche Verr.num

 

Sujets relatifs
Touche entrer qui valide le formulairevalidation d'un formulaire ajax via la touche "entrée"
Valeur touche clavierSaisie clavier sans retour chariot
[shell] Redirection entrée standard clavierOrdre des paramètres d'un GET (avec une touche de Domino et d'ExtJS)
besoin d'aide pour associer les touches clavierevent clavier differents sur une meme page
[mysql] Aide pour l'activation 
Plus de sujets relatifs à : Activation clavier touche Verr.num


Copyright © 1997-2022 Hardware.fr SARL (Signaler un contenu illicite / Données personnelles) / Groupe LDLC / Shop HFR