|
转载:
% }" w+ Q) L( P+ L3 X' I! t2 P# k来教你如何在vb里嵌入汇编!+ ~% J2 q7 b7 Q/ j% I7 n
作者: wl3000wl ( E+ o, d0 }0 K( o$ W( H0 j
本贴绝对值得你珍藏.
d2 S: C& ^9 I# |下面的例子完全用VB进行ASM编程的示例,本例获得CPU ID.
9 s1 \6 Y* m4 T0 e- C5 J工程文件分为一个form1.frm 和一个模块module1.bas0 p+ ]3 I( ~% k$ l/ ^
----------------------form1.frm的源文件---------------------/ R) g' N2 e" U) V
VERSION 5.00
4 d& \5 V* M' j6 P( V/ l& E$ J" TBegin VB.Form Form1
+ `* D% C0 S: M \7 n Caption = "Form1"3 W! L6 k* M3 e9 G
ClientHeight = 1965
7 y4 m' B( ~; _. ?) Y" K ClientLeft = 60" ?" O" n2 h1 L9 J6 q
ClientTop = 345/ r1 ^% h( c7 o) |* G% q
ClientWidth = 3105
) }" |1 T. w2 p5 H) { LinkTopic = "Form1"2 m; y$ [$ |' a% X2 N
ScaleHeight = 1965
$ M5 d2 m2 c; [. o) w0 e ScaleWidth = 3105
0 Q3 X c7 g) [6 G0 r3 N StartUpPosition = 2 'Bildschirmmitte- e, ]1 u! A; s$ x1 x
Begin VB.CommandButton Command1 + n6 t$ S/ ?/ h- r: X6 [. y* y+ h
Caption = "Get CPU Name" A+ A* ]) c0 \! x* f9 F( H
Height = 4958 M1 @" I+ i1 q8 V3 a4 Z
Left = 840
, u7 u+ P: Q! c, M n5 _) U TabIndex = 0$ I6 f5 E, a4 Y5 H1 t
Top = 315/ k X) T* i2 H4 |- ?9 P0 b/ H
Width = 1425
. y- _4 T& g% b End
# m5 {! r% ]) _$ H# n; a Begin VB.Label Label2 ) q0 g/ L+ ]4 O) D/ Q: c) M% l5 _
Alignment = 2 'Zentriert* ^: d+ B: {9 P" t& h
AutoSize = -1 'True! `% l: {: G5 i& O
BeginProperty Font
& S; b& y* P! T2 `5 V Name = "MS Sans Serif"3 @' H$ r9 |( n/ D5 J2 M
Size = 9.75
, N3 x( A' T' z3 W Charset = 0
5 C& t s& }* l4 \ Weight = 4008 m# C, F8 f0 E
Underline = 0 'False, B1 R, d% Z5 V, ?+ B5 n, \: b
Italic = 0 'False
& d! `. V0 @: W+ H$ J; ` Strikethrough = 0 'False1 |* b: u6 h V1 M6 p/ G1 N
EndProperty u) ^- f* Q, Q% S
Height = 2405 U3 Z Y# O: M% `( p1 z" X* `
Left = 1515
% [' L! p7 N. [8 u7 W0 D TabIndex = 21 o8 N2 R2 E7 ?; [, m
Top = 1065
7 x4 R3 l- ~! K1 [' ^ Width = 60+ w1 a. \2 V& z- Y% a% Q6 r
End! \$ y/ r; N3 @+ [ V
Begin VB.Label Label1
: u1 T7 a0 a& u$ u Alignment = 2 'Zentriert
! ] M8 A* u" v/ ^$ S3 p AutoSize = -1 'True
6 w6 {0 Q2 c5 \* y& \- w ~ BeginProperty Font
6 r( N: h1 K8 R1 w4 t/ k Name = "Arial"7 B3 E; g$ @- T6 p7 \
Size = 12
) F% f5 A% _& o4 p$ i Charset = 08 v3 c) l+ M6 B- a! k* V0 z& \
Weight = 7005 |% r$ x) n$ i& F
Underline = 0 'False
2 z4 c$ {& Z" `" t) F- E! k Italic = 0 'False
& I* L1 Q7 h7 F0 b$ [( H9 C Strikethrough = 0 'False
/ {6 T+ C+ ~1 l3 \* j- @ EndProperty
; E. h* G& v6 W/ R" A Height = 285
0 V8 g7 R0 y F! s6 J6 M/ K" V Left = 1515
2 f. _0 j/ I+ q& O- ?( r! Q- U TabIndex = 1
" X) P* s! y( k+ W. e Top = 1350
6 ]7 o( \# Q. Q0 {9 K8 a Width = 759 z, |; G0 M( R; i4 K
End6 K2 e; y B* {. t% s
End- @; m4 X) j0 x# e% X" S6 Z
Attribute VB_Name = "Form1"
1 @: w# }7 t* A3 {2 \Attribute VB_GlobalNameSpace = False
8 [; |6 @) N1 }, mAttribute VB_Creatable = False8 B$ J+ H7 Z0 h1 t7 m: ?
Attribute VB_PredeclaredId = True
8 O% k" a" N0 r( ^ Z( ZAttribute VB_Exposed = False/ [7 X E7 Z2 d4 ^& ^( U* i
Option Explicit" ]# R4 @6 h' t5 h
0 z! i% h& ?0 {1 Q0 u
Private Sub Command1_MouseDown(Button As Integer, Shift As Integer, x As Single, Y As Single)
. X7 Z V1 ]1 R/ p. A B0 _
0 ^, x9 N* P( I* q2 f Label1 = ""% u( P4 e2 p! m" h q7 Y {
Label2 = ""
( c2 E$ k# S8 i* U; d5 @4 t s0 P3 X$ c" i9 t. U
End Sub
! ]. Z' @$ t& N* w$ r
& ~3 V! A) ]: k' W( }$ QPrivate Sub Command1_Click()" M z* O2 `. F) }# T/ ^0 e. g5 f
$ w7 y6 d! I* U B* L; r* D# f Label1 = GetCpuName() & " CPU": @' U& S! v7 `7 B) @
Label2 = "You have a" & IIf(InStr("AEIOU", Left$(Label1, 1)), "n", "")
0 ^% Q) {/ x. ?% m
& z3 k L+ X: H# Y7 p1 @End Sub
1 \ L: S+ Q. L------------------------------end---------------------------------
3 `! m0 a$ Z$ r- `* D7 \' ^4 p; j2 A
; e9 _. g9 |( [9 R C
) \" k1 m/ E$ f2 x) J/ e+ \9 Q$ ^
: u4 l" W; K; Y* j/ r
& p; \5 Y6 I; K: l* k2 h% }下面是modu1e.bas的源代码3 Q+ p9 Q; }/ B6 I3 i4 ^
; B4 I7 @7 Q [/ m" y----------------------module1.bas的源文件--------------------------% r% l+ { h5 x6 ~! H5 R& H' u
Option Explicit
( D1 z+ k) v2 {" E9 Z1 x# D! ?$ }'2 y N. s c6 p Q, b7 B. ]/ y/ B
'This shows how to incorporate machine code into VB
5 b) Z" X: j6 }/ q2 k, ~'''''''''''''''''''''''''''''''''''''''''''''''''''
% w. r- u& x" r& G# u, f! o1 G& w'The example fills the array with a few machine instructions and then copies' u: A: _6 I6 w! Z# v
'them to a procedure address. The modified procedure is then called thru! F% x( ] w* J8 C' C, n
'CallWindowProc. The result of this specific machine code is your CPU Vendor Name.
! I+ [6 \) q- G) x0 V# K'
( W+ q% P% W9 ] {'##########################################################################6 g" P; e/ a# R
'Apparently it gets a Stack Pointer Error, but I don't know why; if anybody1 R% L/ _ b: a3 j
'can fix that please let me know... UMGEDV@AOL.COM- ^; M) h2 W% t2 B9 }& m
'The Error is not present in the native compiled version; so I think it got0 g! o+ Y" U P
'something to do with the P-Code Calling Convention (strange though)..., ~' c6 J. W3 I# q5 n
'########################################################################### s0 t' J' ]4 @
'/ ]& x: m/ c, {8 f6 t
'Sub Dummy serves to reserve some space to copy the machine instructions into.. G! L N- G% n+ O" Q1 u- b2 u. Z
'7 L0 X; M |2 o# s0 p( ]; ~! \
'6 F0 ?) Z* f; ~" u9 ]
'Tested on Intel and AMD CPU's (uncompiled and compiled)
% M5 `0 T6 V6 D0 \'3 p& ]( t x- @% t) L3 k
'5 v0 O- Z! [/ h. c L
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
! _) `5 L; s0 a) j, u- M0 [+ f- jPrivate Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpvDest As Any, lpvSource As Any, ByVal cbCopy As Long)
g% @1 X9 j2 f* P1 U$ _Private x As Long3 K6 B) W4 e) q, u6 o& s+ Z& a j
6 k) N! P2 M/ l G5 K6 G7 |
Public Function GetCpuName() As String5 H0 ]0 l" @. S% M5 y1 l. J
" C- b8 _5 q8 P6 U Dim MachineCode(0 To 35) As Byte: X1 }& l* @) R$ ?; I" L2 @7 g
Dim VarAddr As Long( V+ l6 _8 ~) o6 M: O, [# x
Dim FunctAddr As Long
. U! s9 j% y. o7 N" m Dim EAX As Long) z1 c/ p5 J' E
Dim CPUName(1 To 12) As Byte- G0 ^8 u$ @& J* a+ {3 S0 j9 g3 ~
- G) r# U m! F( h/ H/ v
'set up machine code3 d, _: J7 k/ i, Z; B
/ I# T9 k* G# T& L+ Z$ z5 G% W* n MachineCode(0) = &H55 'push ebp- s# |6 p4 q" ?/ t8 Z/ ~' R6 z
+ N4 a2 l5 `1 C9 i( \+ y! j MachineCode(1) = &H8B 'move ebp,esp- u2 N& L4 `1 V- e0 B! ~1 D
MachineCode(2) = &HEC
4 E1 }* W+ F+ Y- k8 _
! ]% T' r" ^# \) s MachineCode(3) = &H57 'push edi
9 A. f' F' C) K, V q 6 i0 {3 j/ C' B1 \- J% O1 j" r" J
MachineCode(4) = &H52 'push edx
9 ^1 _1 l* w, c 6 \$ a4 A" }2 l* L5 d: |7 r
MachineCode(5) = &H51 'push ecx& K1 n/ w/ Y, @% a6 D# D
^- M l2 z% L" U8 w5 o& U5 ], E
MachineCode(6) = &H53 'push ebx1 G; F# M! R; T$ Q" a
& B- o/ Y* q/ u8 M0 H3 w MachineCode(7) = &H8B 'move eax,dword ptr [ebp+8]
$ V1 @7 K9 U) ~7 a5 e8 N MachineCode(8) = &H45. ?: u1 U. |( v# f+ h. N/ d
MachineCode(9) = &H8
8 t, r" v% c' q3 w1 J7 X- C 0 z0 H( ^! M; Z- O' d9 A7 C! \
MachineCode(10) = &HF 'cpuid
5 X' r# {8 Y T9 \7 m MachineCode(11) = &HA2+ F1 q+ v' N2 ^
/ y. G9 i* a# C MachineCode(12) = &H8B 'mov edi,dword ptr [ebp+12]: c. ?! e: j) t8 O/ H
MachineCode(13) = &H7D
* |4 R5 y" ]8 I% o MachineCode(14) = &HC
6 M* U) `: U/ `; [* j
9 s& w2 c0 Q# ~8 @ MachineCode(15) = &H89 'move dword ptr [edi],ebx# O, Y! |$ Q2 z. t0 V
MachineCode(16) = &H1F' w. q; K. h! J( A% m
. K4 \# \5 b; E, [0 I8 M5 w' B t, ^
MachineCode(17) = &H8B 'mov edi,dword ptr [ebp+16]. q9 Y2 [7 \# I1 [/ V8 W
MachineCode(18) = &H7D3 m$ e- p F7 b( Q. k2 h! l, L
MachineCode(19) = &H10
) u# K5 |9 T# W0 M" n) |& L 2 N. X' k7 g- h0 X3 N" B
MachineCode(20) = &H89 'move dword ptr [edi],ecx3 T& ~+ o' ~$ E" Y: l
MachineCode(21) = &HF
- N& h' ]/ s3 S& U, T
$ H/ }( t, C3 r MachineCode(22) = &H8B 'mov edi,dword ptr [ebp+20]
7 t1 S: V; f1 ]" o MachineCode(23) = &H7D
% J {- }% A( u1 |8 p& @ MachineCode(24) = &H14
) G! m+ A- z3 @( F2 D" }- a8 _
: _( P. ?4 H: u$ R: V. S MachineCode(25) = &H89 'move dword ptr [edi],edx
( @8 J+ |& S: ~, s# h2 }4 f- n MachineCode(26) = &H17
- U; D6 p/ [ U% \7 J 8 o' \2 W* X$ k/ |/ y
MachineCode(27) = &H58 'pop ebx
5 y4 L0 a4 ]: B- O- r+ i& u/ o* B9 d. D% L( f9 z- ]
MachineCode(28) = &H59 'pop ecx4 o' t* `2 N1 r; l* f) v
7 d9 c& D0 l' y" @7 G! \, c
MachineCode(29) = &H5A 'pop edx5 s* p& M3 J5 _2 E) j0 I3 r4 j
2 a( N- j' g9 ?9 U2 \; f1 N6 M MachineCode(30) = &H55 'pop edi4 C# N" T1 Q, s
) W% i) {+ O" O7 j5 }
MachineCode(31) = &HC9 'leave' v5 }& b: e/ L9 a G
2 p/ x4 q( E+ Y2 U, X4 ?( r0 ?) J MachineCode(32) = &HC2 'ret 16 I tried everything from 0 to 24
4 V5 Q( z! t& Q' w0 M8 x$ Q MachineCode(33) = &H10 ' but all produce the stack error, g, N) L, q4 Y5 Z: M
MachineCode(34) = &H0
. B4 b; J; j- f* R4 Z! X 3 n0 ~) J* P* F$ X' a* w- L
'tell cpuid what we want8 j* }2 x4 }: o# w- R# n
EAX = 0
, z' C* r, |0 \8 r3 ^7 f 6 J0 ^9 J" _& v! {/ x7 b# D
'get address of Machine Code+ T7 u# k; ] P% E( c; U o
VarAddr = VarPtr(MachineCode(0))( m9 G; A/ A- l+ [( }4 U
* `) V$ o: t p5 b+ N; B 'get address of Sub Dummy% a" f3 i& o6 A. T5 N
FunctAddr = GetAddress(AddressOf Dummy)0 n3 h, o: Y/ H. k+ ]5 Y; Y% ~# o
8 W( M; d: @* ^: @
'copy the Machine Code to where it can be called- O! o+ g: ~1 ^% s- ?2 d+ _; ~
CopyMemory ByVal FunctAddr, ByVal VarAddr, 35 '35 bytes machine code
6 X$ ?: p7 A& b: L2 I 5 Y8 y& g) R6 r8 s
'call it
% C+ ?* b& x& z On Error Resume Next 'apparently it gets a stack pointer error when in P-Code but i dont know why2 K; s+ K3 _* T6 S6 C" N8 X
CallWindowProc FunctAddr, EAX, VarPtr(CPUName(1)), VarPtr(CPUName(9)), VarPtr(CPUName(5))
4 a8 D1 P" c* V. F( n 'Debug.Print Err; Err.Description1 B( G2 f) E% a' S
'MsgBox Err & Err.Description
1 l, m4 U; J7 w% O6 |8 _, k On Error GoTo 0
7 x: c2 n& u/ a2 s; I; f4 w, w* X) }
. D) }! P4 C! C Z GetCpuName = StrConv(CPUName(), vbUnicode) 'UnicodeName! D. @+ ^. ?3 A9 w- }4 ^
, Q7 Y: a, M; o+ H& cEnd Function* u2 \$ @( O0 w( `
+ \$ b3 U6 n. |+ n% g
Private Function GetAddress(Address As Long) As Long
' N; n0 w; J3 Y" Y6 p) g! K- P) S: x: F [ ~0 Q4 w
GetAddress = Address
" n0 F: M" e4 }5 u' E) z. \
. Y, E4 K$ R7 s" n7 ?& o) xEnd Function
% i5 F6 b4 k2 _) Y9 I' a% j0 p( H% C7 H
Private Sub Dummy()
! O( ^* x3 u( {' d' [- x
# B: U' `/ J: E. ^) U 'the code below just reserves some space to copy the machine code into
5 S- @# U* a! Z& ^0 S1 S 'it is never executed
, \/ ?! d2 R6 ~% P9 d- k4 \9 Y4 S9 g/ ]; p" V }1 c$ }) D6 I
x = 0- a3 J6 T: J: h1 a
x = 11 D& B* a$ [: f) Z9 U& W
x = 2
- B" Q3 x% M6 l3 D x = 32 [8 w3 m: i( V. a# H7 |7 e) F
x = 4
. ^- w/ d$ F* ]- x1 I x = 57 n; ~) m3 w" a8 r- }# B
x = 6
7 h/ U) S* n! T4 \2 o- X4 \ x = 72 A' }$ r! i* |+ F% V
x = 8
- [" g) W7 `2 X. b) j% K# g x = 9
- B% Z' H3 h2 v3 B) H3 o E x = 10) ~8 y# N; g O$ D0 Y+ Q* y0 A
x = 0# j7 |* N$ ~7 q- Z- I
x = 1$ _# O9 ?- z2 n$ h
x = 2# s4 a, K+ I) T# U" }! U- k
x = 34 T( B/ I( C, \; R+ F2 S5 N7 L% n5 r. o
x = 4
7 i0 z$ ]9 ]8 B x = 5: s0 M& ?( d8 x6 |* B4 h9 e% O" ?
x = 68 o" n# h. x2 K5 J) [5 [6 q
x = 7/ m2 ^8 `! E- Q+ q. m! y$ B- |3 j/ ]
x = 8* q3 }: y+ x) v, \
x = 9 Z9 }+ g$ J2 [
x = 10, m, R; [3 Z. U7 M
( a* f3 x! N- C( A) k. D
End Sub
- i" a2 N2 ^( R! l. ]: G------------------------------end--------------------------------------
" M! I6 P S' K+ ?0 Y8 e3 b/ z
( D. D9 c. g+ R) @ ) R+ |% A3 _4 ~1 d
0 u) f* R* A2 Z0 z1 s
|
|