Skip to main content

[archive] simulate alt-tab

  • March 2, 2010
  • 5 replies
  • 0 views

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*

5 replies

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*
One thing I can tell, is that the 3rd paramter to keybd_event is a DWORD, and should thus be 4 bytes, not 1 byte.
For this you should use PIC X(4) COMP-N.

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*
Darrell,

You might want to check out the W$KEYBUF routine. Not sure if it will work for ALT-TAB, but it looks like it might. Here is an excerpt from the manual:

You may specify special keystrokes by placing code names in curly braces. Within curly braces, you may use the caret (^) to indicate Control characters or the "at" symbol (@) to indicate ALT characters. For example, "{^M}" indicates Control M and "{@L}" indicates ALT L.


Paul

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*
Darrell,

You might want to check out the W$KEYBUF routine. Not sure if it will work for ALT-TAB, but it looks like it might. Here is an excerpt from the manual:

You may specify special keystrokes by placing code names in curly braces. Within curly braces, you may use the caret (^) to indicate Control characters or the "at" symbol (@) to indicate ALT characters. For example, "{^M}" indicates Control M and "{@L}" indicates ALT L.


Paul

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*
Darrell,

You might want to check out the W$KEYBUF routine. Not sure if it will work for ALT-TAB, but it looks like it might. Here is an excerpt from the manual:

You may specify special keystrokes by placing code names in curly braces. Within curly braces, you may use the caret (^) to indicate Control characters or the "at" symbol (@) to indicate ALT characters. For example, "{^M}" indicates Control M and "{@L}" indicates ALT L.


Paul

[Migrated content. Thread originally posted on 26 February 2010]

has anyone simulated alt-tab key combination to switch the active process under windows. This can be done in VB so I would imagine someone has done it cobol. I believe its a call to USER32.


Visual Basic routine: WORKS!!!


Private Declare Sub keybd_event Lib "user32" (ByVal bVk As _
Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal _
dwExtraInfo As Long)
Private Const KEYEVENTF_KEYUP = &H2
Private Const VK_ALT = &H12
Private Const VK_TAB = &H9

' Grab all of the text in the WebBrowser control.
Private Sub Command1_Click()
' Press Alt.
keybd_event VK_ALT, 0, 0, 0
DoEvents

' Press Tab.
keybd_event VK_TAB, 1, 0, 0
DoEvents

' Release Alt.
keybd_event VK_ALT, 0, KEYEVENTF_KEYUP, 0
DoEvents
End Sub


Cobol routine: DOESN'T WORK!!!

000150*
000151 01 H-ACU-WND PIC X(04) COMP-N.
000152 01 VK-ALT PIC X(01) VALUE H"12".
000153 01 VK-TAB PIC X(01) VALUE H"09".
000154 01 VK-RELEASE PIC X(01) VALUE H"02".
000155 01 VK-NULL PIC X(01) VALUE H"00".
000000 01 VK-ONE PIC X(01) VALUE H"01".
000156*
000531*
000532 ALT-TAB-RTN.
000533*
000534 SET ENVIRONMENT "DLL-CONVENTION" TO 1.
000535 CALL "USER32.DLL".
000000*
000000* Simulate pressing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate pressing the TAB key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-TAB
000000 BY VALUE VK-ONE
000000 BY VALUE VK-NULL
000000 BY VALUE VK-NULL.
000000*
000000* Simulate releasing the ALT key
000000*
000536 CALL "keybd_event" USING
000537 BY VALUE VK-ALT
000000 BY VALUE VK-NULL
000000 BY VALUE VK-RELEASE
000000 BY VALUE VK-NULL.
000541 CANCEL "USER32.DLL".
000542*
000543*
W$keybuf will not work for this.