|
转载:
" }+ p+ r! s p" f; t来教你如何在vb里嵌入汇编!5 m( Y0 H1 t) c# D* E" J8 e$ k
作者: wl3000wl 3 V2 o W! g$ n% c1 _) p
本贴绝对值得你珍藏.
, M5 }7 `+ a( `+ f# n/ f4 M下面的例子完全用VB进行ASM编程的示例,本例获得CPU ID.5 H! N9 ^: m2 Z3 K( i, q- a1 v
工程文件分为一个form1.frm 和一个模块module1.bas
' `6 T; | u8 S, X- A----------------------form1.frm的源文件---------------------
9 b! ?. L" x- @; _; A0 JVERSION 5.00
& d+ A' B0 |3 j1 ? E$ aBegin VB.Form Form1
, G% @7 b9 D8 V4 W" ~+ H6 ~: L Caption = "Form1"
: Y4 n1 N% }) H! \& A& e ClientHeight = 19653 [9 V" T$ J* s; D8 i
ClientLeft = 60, r v6 K M' s# j- q
ClientTop = 345
0 i& @& o1 {% F! S* i9 l' ` ClientWidth = 3105
) i* K$ M8 n8 [ LinkTopic = "Form1"/ e+ s6 g: L/ r, ~1 N, m' e
ScaleHeight = 19654 e! h, d9 o) a3 U
ScaleWidth = 3105
+ @# \; ?; b9 {# ?% H+ c StartUpPosition = 2 'Bildschirmmitte
* P/ g- [' w L* l4 L" K6 x' W Begin VB.CommandButton Command1
" p( m) Q. B% B7 f. ]" J0 t4 z/ [ Caption = "Get CPU Name" ~& a; @9 v0 g+ M
Height = 495
7 Q# o( C W2 S' [9 t5 | Left = 840
, V( f$ U1 d9 B7 b" z TabIndex = 0, x1 w1 w* Z1 b! P1 M
Top = 315
3 ]" H9 X9 b0 C Width = 14253 B* |! D2 |3 M1 [4 t0 d
End! `1 w1 p! I: w7 V2 r: \- H- W* Q2 y
Begin VB.Label Label2 - c6 S1 n0 i6 e5 D/ P
Alignment = 2 'Zentriert' \! h! M8 W; G0 M
AutoSize = -1 'True- Z; ?/ A* L3 q: I+ |
BeginProperty Font
) L m7 l b# C+ M% E Name = "MS Sans Serif"" g5 l6 b, b5 \0 I6 B, Y3 A
Size = 9.75, K9 D$ S7 N M/ n W9 B
Charset = 0
' D' N# D. l4 I0 S% Z: @. [$ \ Weight = 400
% T: y8 B4 E3 i Underline = 0 'False" H; @, @9 [4 O# M+ [
Italic = 0 'False7 B, e+ Q8 A) D+ `" C$ L* P7 Q1 x) B
Strikethrough = 0 'False
/ c4 o6 G' N; D# g, P6 Q$ ]& L EndProperty$ ] ?$ \2 o; Z0 P& y- r
Height = 2408 V7 m; R9 a z# G
Left = 1515! V1 J* @# N& z- T3 s
TabIndex = 2) l% Q P0 e" Q) P. I" p
Top = 1065
' |! C: C. ^+ h. m/ C Width = 601 V! c: Q9 O# x! Y
End q; q8 F4 P: u7 F! B: O3 K
Begin VB.Label Label1 : L+ |& E& q2 B
Alignment = 2 'Zentriert; b" U9 N: n$ I
AutoSize = -1 'True
! r, n( p+ q% m6 j3 V! j BeginProperty Font ) W5 L! C ]1 z/ ?' g1 i7 h' S
Name = "Arial"1 [7 m( B- D+ R. f
Size = 12
' O% J7 }; c1 y1 G+ i5 ]# k Charset = 0
7 t3 t" g$ T8 U$ K2 s. [& g+ R. m Weight = 700/ a' Z3 W& T" B! k7 f6 i
Underline = 0 'False% x m( M2 {- P
Italic = 0 'False
' r8 ~2 _/ [1 w8 s* S Strikethrough = 0 'False
# `% N5 t& J* p* N$ s, B9 V9 U( Q EndProperty+ }* k% h. Q1 p& E: X8 M) f" p, n
Height = 285* R& B/ }: h3 I
Left = 1515
* h8 a8 E* U+ A1 a0 B, q9 | TabIndex = 1
3 V6 z% C) [) x. `. Q Top = 1350& \4 m+ e" K/ f& r+ J
Width = 75
3 P* f+ o9 ^2 ]8 W End
* V7 |& X9 l: b H4 S7 h( HEnd# Q7 z- y. R; Y, J; \- f: f
Attribute VB_Name = "Form1"" K' i- C( e( p1 Q8 n1 h/ b+ k* l
Attribute VB_GlobalNameSpace = False% i/ ?1 V# e1 A5 y2 E7 O4 U, }" L
Attribute VB_Creatable = False
; {( d: I0 Y h4 w. d8 L$ |8 CAttribute VB_PredeclaredId = True
4 X- I. L/ H0 nAttribute VB_Exposed = False1 o" e! b/ n) w) n
Option Explicit( R& f6 x/ a8 d$ n
- X. D% v! v& U) v' B+ u
Private Sub Command1_MouseDown(Button As Integer, Shift As Integer, x As Single, Y As Single); O7 Y+ C7 @* S9 k% _* w
& T: w4 K) a, u
Label1 = ""
) B/ u' ?) @; N$ A7 l7 B Label2 = ""
7 v* Z' O0 |1 S+ D) G) y; v/ }# ~0 d" n6 f
End Sub
7 `2 D; r. G* Y) ~ f
9 i* [9 M' x7 O6 g! u8 UPrivate Sub Command1_Click()$ g* M( H! \$ [+ ]/ K
# T" b% J) e! I- B) `1 ~ Label1 = GetCpuName() & " CPU"6 h- y6 p: p2 H4 L/ m2 {0 f9 q
Label2 = "You have a" & IIf(InStr("AEIOU", Left$(Label1, 1)), "n", "")7 Y. Z0 { Z/ z8 u( u
7 p" l g2 ^3 T; u% @1 \ SEnd Sub5 L' d2 u) D' D; i
------------------------------end---------------------------------
2 `9 S# L* B, O6 }/ u8 y0 t8 f
% w' x/ J) x$ E! T" M: G% ~7 f/ v" T) [, R4 O: _) l
, F: Y( t9 E- P4 Q. j
0 f0 K5 Q* o: q+ c3 _/ p1 J$ G
# F5 n5 M3 K, N& c+ O8 T- |$ P5 A下面是modu1e.bas的源代码
. _0 w1 n: O& h
3 s3 @7 h; V8 U- T! {0 R/ u" H----------------------module1.bas的源文件--------------------------
/ a1 x1 o7 K& jOption Explicit0 g2 J7 D8 \. R
'
" m& H% a, J! t) @: U5 v'This shows how to incorporate machine code into VB
7 {+ J2 A0 X1 a: W6 {5 L'''''''''''''''''''''''''''''''''''''''''''''''''''
/ [* _! ^# k% X7 T [3 Y- v'The example fills the array with a few machine instructions and then copies7 o( G. j% z' P/ C: n# v
'them to a procedure address. The modified procedure is then called thru; l+ M$ g$ J6 z+ j. M
'CallWindowProc. The result of this specific machine code is your CPU Vendor Name.
1 Y6 Y6 X' J$ q5 e'4 M# j8 g0 m% o2 d6 k6 }; ~
'##########################################################################
# y) ^. d; P; B) H; G1 N' e'Apparently it gets a Stack Pointer Error, but I don't know why; if anybody2 w5 ?) G9 r( p! S" X
'can fix that please let me know... UMGEDV@AOL.COM& [6 K# M {9 n
'The Error is not present in the native compiled version; so I think it got
5 y& s) V' }+ h'something to do with the P-Code Calling Convention (strange though)...6 H B! N) a' _$ w. T' T* ]# _
'##########################################################################; i+ q. D( w n3 z9 M k
'" z5 B9 m( g6 s' e2 U/ f& K
'Sub Dummy serves to reserve some space to copy the machine instructions into.
4 c G" J+ d% s7 I* P# ]& K, C% B2 F'4 @/ O3 S" z7 E p
': x" g6 [( S/ s9 Y! Y4 e7 y
'Tested on Intel and AMD CPU's (uncompiled and compiled)$ Z# B1 U* s1 D8 A0 w/ R4 q
'
) Q4 p, z5 m2 F& J2 y. l' {'
9 w- [/ \& [$ l7 T# |$ k6 mPrivate 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( |1 K8 @) f8 _8 Q0 S
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpvDest As Any, lpvSource As Any, ByVal cbCopy As Long)' ?% l" }3 h3 L' [9 X1 h
Private x As Long
, \' L: T; ]4 M7 k1 H
) K/ y2 l0 v: w- zPublic Function GetCpuName() As String
" Y! {2 p& [9 F, n
8 }% o2 `2 n; W Dim MachineCode(0 To 35) As Byte
1 Q* z4 |: z+ g( g0 j9 G: E Dim VarAddr As Long
6 }8 j1 W W* o Dim FunctAddr As Long; G4 `% ~5 x' O) b$ D
Dim EAX As Long
+ X" K( Z: I4 U# ? Dim CPUName(1 To 12) As Byte
8 s3 C2 v2 B$ \6 Y $ J' }3 ~% {& Z( a! c0 B
'set up machine code* v5 M& Q! n/ {1 u& v' C2 d
+ ?9 L3 F! r+ m4 `) Y: k MachineCode(0) = &H55 'push ebp r4 N' E& O/ e n# _. i9 }% l
. [/ |: @* F! D. V- {6 x MachineCode(1) = &H8B 'move ebp,esp
# {+ j K6 e( b+ ]3 O' C. ] MachineCode(2) = &HEC
: j; g ^( V# j0 D
3 O8 Q3 E1 y3 w# K1 h: v, R4 F MachineCode(3) = &H57 'push edi
" F9 D( S8 _* _' [ ) i u& B6 G9 h6 M; [
MachineCode(4) = &H52 'push edx
1 A8 a5 l! z6 l' K# g: _ 0 ~/ w1 z% }. ~
MachineCode(5) = &H51 'push ecx
8 g+ D5 s' H) w 9 D( j. F5 ]+ I4 u: t( ]
MachineCode(6) = &H53 'push ebx
4 x$ [7 ]2 u" ]* T
8 h( H& y+ d# K MachineCode(7) = &H8B 'move eax,dword ptr [ebp+8]
9 _, p% D \% L) h MachineCode(8) = &H45
* D' ]- L4 H2 h- P' q MachineCode(9) = &H8
" k5 X# J5 W, U
0 j# h) F0 ^& K7 O$ i MachineCode(10) = &HF 'cpuid
- A' D3 K, [0 h1 A& ?5 B0 Q7 [# c MachineCode(11) = &HA2! H* b% E8 f# K9 s% d7 U' X
f- C6 W: D t2 ~( ^2 {7 Q9 [& _
MachineCode(12) = &H8B 'mov edi,dword ptr [ebp+12]
# O6 m$ V1 _- e& M( t8 B1 O2 [( J MachineCode(13) = &H7D7 b! A0 f! J) n" ?6 f
MachineCode(14) = &HC( T" w: V/ w7 W6 b" A
4 I' I7 R; f2 R( A0 h$ s, B MachineCode(15) = &H89 'move dword ptr [edi],ebx
5 d" _ {9 A# P. s MachineCode(16) = &H1F
% r" T( l) p0 U9 @
) N2 U# }. S1 v7 ~+ `2 V MachineCode(17) = &H8B 'mov edi,dword ptr [ebp+16]
+ v" u3 M4 L) N) j$ Q MachineCode(18) = &H7D
. ]4 i, I7 a% q8 F( J# r MachineCode(19) = &H10
* o! w" r* c6 [# X " x6 p# }+ J% a. {1 D" p
MachineCode(20) = &H89 'move dword ptr [edi],ecx4 m& u/ P9 J m$ P* ]
MachineCode(21) = &HF
; y9 u7 l5 X1 A- p: S9 X8 j0 u2 q 9 h- }" s( e) T, G$ {- ^2 r- m4 e
MachineCode(22) = &H8B 'mov edi,dword ptr [ebp+20]' Z3 L! x" @4 h S @
MachineCode(23) = &H7D
* S& p5 h" j- e* {. `, k MachineCode(24) = &H14
3 @ U+ K/ K" c! y' R 5 g" `% D, w5 o V9 y
MachineCode(25) = &H89 'move dword ptr [edi],edx
: `7 X5 d, ^$ X, I5 b MachineCode(26) = &H17
3 N1 C; T6 q, l1 t( _5 O - @: h2 k8 K. b. {8 g. X3 ?$ e
MachineCode(27) = &H58 'pop ebx
# ]4 P4 f' |6 F( [+ w- a4 |3 M6 b& p! g
MachineCode(28) = &H59 'pop ecx
A3 [2 f) u) b' k/ u2 \1 N- l( ^; m8 x/ V( G. m
MachineCode(29) = &H5A 'pop edx
6 E& f2 y0 k6 {! I& m0 x2 o7 C2 a
@. H7 d( _- A( o; l- n MachineCode(30) = &H55 'pop edi7 J; U7 n& Q/ M' y
- ]2 }2 c: n# E2 {7 e9 f) f O
MachineCode(31) = &HC9 'leave7 ~/ V k5 Z) L4 @, u/ ~
6 U2 N! r+ b7 o+ e
MachineCode(32) = &HC2 'ret 16 I tried everything from 0 to 24
' X/ [- Q8 n% m! @$ E K! v2 I( i MachineCode(33) = &H10 ' but all produce the stack error
$ \; q; Q$ [. N# B* k MachineCode(34) = &H0
/ k; n9 ]" T* F& w( P, W 2 J( j T1 F% e" p0 ` T
'tell cpuid what we want
" d9 y: I! Y8 L( O* r2 [ EAX = 0
3 x" K! m+ l9 p0 M7 U& J
: `- @4 \* t% f1 ]2 P T/ r 'get address of Machine Code
8 Z7 ?1 r' @, F2 m4 } VarAddr = VarPtr(MachineCode(0))0 y p( |- \' S, y2 R7 n c7 D/ U4 `
/ s2 \8 @6 \3 N4 f; _
'get address of Sub Dummy* H3 ?2 o+ Y$ h0 \3 b
FunctAddr = GetAddress(AddressOf Dummy)% U T7 N5 ^3 x. b! {
- Q4 L4 ^! _& A
'copy the Machine Code to where it can be called% e- k# q! c7 N6 T7 n
CopyMemory ByVal FunctAddr, ByVal VarAddr, 35 '35 bytes machine code; ^' R+ p F3 m) O9 U
$ B/ K, B" w, i, I- u
'call it" J9 h' b1 X% b4 Z
On Error Resume Next 'apparently it gets a stack pointer error when in P-Code but i dont know why
2 t7 h% G" R$ u u2 a, U CallWindowProc FunctAddr, EAX, VarPtr(CPUName(1)), VarPtr(CPUName(9)), VarPtr(CPUName(5))
$ N1 V" P& S$ N$ f; d 'Debug.Print Err; Err.Description7 r! d. k% ~# L! w7 p
'MsgBox Err & Err.Description ?4 J) }$ B6 e' k& T- U7 K
On Error GoTo 0
7 ~5 G9 s; R9 e% W; d& {/ J ! L! ~# x3 t8 \8 e5 E" K7 T% k
GetCpuName = StrConv(CPUName(), vbUnicode) 'UnicodeName8 M$ d' P; Q. w- J' b" r1 J
) L8 {0 ^8 I8 V6 N& c
End Function* c0 E3 ], a% [6 {; R
- i, ?. l# W# `2 x) c" A# |
Private Function GetAddress(Address As Long) As Long
! i k% P( j* t
. v( u3 M: B6 G- K2 A% m( P GetAddress = Address+ d6 Y+ _% ^7 m2 ^ x
4 g8 I H. g4 ^End Function6 S2 f2 \2 y# i9 _! d8 Z* K
7 Z* I+ v. _/ g: ]( ~. K
Private Sub Dummy()2 h& r& F! _" v3 Q4 s7 M9 E9 j- J
) t$ S7 T& j% E8 s
'the code below just reserves some space to copy the machine code into0 G& Z. ~" M" @
'it is never executed
3 A8 f8 t+ v0 _) G% Z6 a. I! h
: a: d4 R( \( A4 } x = 0
- `. h# b% S z$ Q3 }8 | x = 14 G3 L. I3 z d# O. P, L% |: @
x = 2
, N& n' E5 `# U7 K8 g$ v x = 3
0 C& d% L: y; b4 ~7 u4 j0 ^( } d x = 4
# {$ c# @5 w. D: S6 a2 t9 W3 Q% J x = 5
) }" [+ u: A8 W x = 6% n5 K1 g7 w8 m+ H/ |
x = 7
/ h' I2 q) c' _9 D% w x = 8
' }0 b Y$ z: l6 | x = 9 _% F( C- M2 M3 [7 n* e# O3 s( q1 A
x = 10/ R2 _# ~. q$ h: _
x = 06 h; Z$ V: O" m# Z' ]% i, y
x = 1
* ^/ \' u' n3 y x = 2
, W$ P3 u4 q) P; S. i5 E x = 3
! [! K/ U! _0 Z( J! C" |$ f O2 a x = 40 F, G! u7 h, _# y
x = 5
) H1 [$ W* S0 b/ ^$ [ x = 6
4 P$ E+ l1 U/ T2 B; S& P: g x = 7
6 Z8 S) q1 C+ w2 W1 o0 j% g x = 8; p( o. A+ n, V$ `0 t, `
x = 9# F/ K/ i) U1 o1 X7 X' x* c
x = 101 U8 V# \) }! d
: f, ]+ {; | C. @% V
End Sub
* [# j* T7 I% U i4 n; p+ w! Y------------------------------end--------------------------------------2 K- p" l, P' P. {" R
t0 \( O7 X( Z% E4 J2 C
; |* A8 W! T' o. i' [1 Z' p& ]9 L7 D+ i' f) J( w5 T
|
|