下沙论坛

 找回密码
 注册论坛(EC通行证)

QQ登录

QQ登录

下沙大学生网QQ群8(千人群)
群号:6490324 ,验证:下沙大学生网。
用手机发布本地信息严禁群发,各种宣传贴请发表在下沙信息版块有问必答,欢迎提问 提升会员等级,助你宣传
新会员必读 大学生的论坛下沙新生必读下沙币获得方法及使用
查看: 3591|回复: 3
打印 上一主题 下一主题

请问VB调用我汇编写的函数

[复制链接]

该用户从未签到

跳转到指定楼层
1
发表于 2004-2-7 15:59:00 | 只看该作者 回帖奖励 |倒序浏览 |阅读模式
我写了几个函数,VB调用后会出错,我自己汇编写的则不会
+ S- y. @* P, Y# E2 D我是恢复了ESI,EDI寄存器(在WinAsm32附带的一个帮助中说要恢复,EA/B/C/DX则没有要求),老是出错(全部恢复当然就没错了).不知道他还有什么要求,知道的告诉小弟我啊!
分享到:  QQ好友和群QQ好友和群 QQ空间QQ空间 腾讯微博腾讯微博 腾讯朋友腾讯朋友
收藏收藏 分享分享 顶 踩

该用户从未签到

2
发表于 2004-2-7 19:21:00 | 只看该作者
你用DEBUG程序跟踪一下不就知道原因了么+ T. m+ `/ {9 w3 d8 D2 b: Z1 y
既然全部恢复不出错了,就用pusha/popa好了,省事。
3 [) v( j( s2 ]1 c对于VC程序,ECX常用于函数间传递this指针的,VB就不知道了

该用户从未签到

3
 楼主| 发表于 2004-2-8 19:42:00 | 只看该作者
谢谢呀!

该用户从未签到

4
发表于 2004-3-19 17:50:00 | 只看该作者
转载:
( Y" {( k1 h: m9 h来教你如何在vb里嵌入汇编!
8 n0 n3 H3 Y, g. ?) }作者: wl3000wl 3 r  c0 `+ [" ^) i+ ]
本贴绝对值得你珍藏.( T) V4 U+ d! w- x
下面的例子完全用VB进行ASM编程的示例,本例获得CPU ID.( e& |  x' }$ O
工程文件分为一个form1.frm 和一个模块module1.bas
$ |$ P; B+ U& x5 K----------------------form1.frm的源文件---------------------0 z- n/ M; d0 j4 R# I
VERSION 5.00- @! X7 P9 j* n+ Q2 h0 P  e  [. x
Begin VB.Form Form1 0 o+ H$ y$ x; c" I. ^
   Caption         =   "Form1"
) ~5 @: e1 @$ p# D" o/ U- P% B   ClientHeight    =   1965
; P, h( i$ s, f   ClientLeft      =   60
* F8 W( C9 @% t1 ]   ClientTop       =   345+ c$ r1 C! R$ Y0 d/ I* Z+ s
   ClientWidth     =   3105; F9 L% l3 n, \) D/ ?- B
   LinkTopic       =   "Form1"% ?. n) o. {1 ^
   ScaleHeight     =   1965
) H. o8 D3 Y/ w8 n1 b& q: Y& p0 T   ScaleWidth      =   3105% }" D7 C. e: J8 D  b9 T& {
   StartUpPosition =   2  'Bildschirmmitte
) I  a% h# \, P7 ]) R1 r   Begin VB.CommandButton Command1 % }/ h( ~" N& i/ `% |+ |, @
      Caption         =   "Get CPU Name"
. n$ u5 U5 l) Q      Height          =   495
* l2 E8 J4 n7 T      Left            =   840
& y; S- \1 j6 d      TabIndex        =   0( a2 }! E# V& k0 k6 X
      Top             =   3157 ]7 X2 r  T- k; n$ X2 ?* ]# B
      Width           =   1425# g# K. c9 k9 L# w. \- Y5 l
   End" |4 h3 A1 G) V2 c; B
   Begin VB.Label Label2
4 n6 G6 x# D  [: h* b      Alignment       =   2  'Zentriert9 z; T- l' o& T8 R9 D* t7 s
      AutoSize        =   -1  'True. E3 L3 C* @7 b3 E5 A; I& f5 r% `4 {$ S
      BeginProperty Font 1 T' y  {7 W- o0 g" V+ @
         Name            =   "MS Sans Serif"3 L6 U) \8 g' {
         Size            =   9.75/ h1 }7 ?, K. j: ^$ f, V
         Charset         =   0. ~+ V; o: N- q, _) F
         Weight          =   400& m( o& \+ U' V, ^7 H
         Underline       =   0   'False1 b4 X& I7 Z1 x/ v* j
         Italic          =   0   'False8 }; G1 g; H' m) k, [& u& G
         Strikethrough   =   0   'False) s, X; A; P" x, L
      EndProperty
) Q6 c. _  C3 m, T4 {      Height          =   240
3 T' ^6 [$ \0 z# H5 T( u$ z; N8 V      Left            =   1515- E% l2 N1 F/ W3 `  z. q2 r
      TabIndex        =   2$ V& |" c: z  j( }5 Z% a- {; s7 n
      Top             =   1065
. b  _/ y  e) E: A6 b/ D1 C      Width           =   60( \# V* j; S* j& Z  z
   End( H, Q" b! E* v
   Begin VB.Label Label1
/ U" O9 X# v/ a      Alignment       =   2  'Zentriert/ c+ L% m- C  b0 \
      AutoSize        =   -1  'True) i% f! o* H( I& V9 n
      BeginProperty Font 4 h+ B, v' P. k" m/ Y6 T
         Name            =   "Arial"
) W3 z, d" g: ^& V4 I3 |, O$ }         Size            =   12$ v, u) D- g8 Z/ U
         Charset         =   0- E2 }- Y4 Y* F' N
         Weight          =   700
  A5 I) }/ t; ]/ _' g5 b         Underline       =   0   'False
8 S4 }7 T0 G. S+ i8 s; t, P         Italic          =   0   'False( \% R: v1 y# U
         Strikethrough   =   0   'False
1 K3 p& y7 G; f6 D7 h; s) x) e      EndProperty; Y7 R( `$ g" w
      Height          =   2851 y2 I6 B! m9 b: P/ o0 Q
      Left            =   1515* j% T9 v" a8 X* b! q; ~! C8 \
      TabIndex        =   1
! w9 q9 R; R# z' v' X/ ~: Y* |' ~      Top             =   1350  i7 V0 n. [% f( c) u
      Width           =   751 ?; Z* P3 Y/ k
   End3 u; I: d0 M8 `# F
End+ s( Z' b, ?8 v. G1 w7 ^
Attribute VB_Name = "Form1"+ r8 O, I2 P; e$ Q
Attribute VB_GlobalNameSpace = False
& S; L2 g* ^% ]; Z2 K4 B6 S0 J- aAttribute VB_Creatable = False
) E% [5 a1 D& s7 `Attribute VB_PredeclaredId = True) a  k% D% E& B8 g/ l, F) e
Attribute VB_Exposed = False
& Y7 A; i  Y% `Option Explicit0 {) _: K* c/ l( F; Y! ]: D
* I  K& U; P  |/ v
Private Sub Command1_MouseDown(Button As Integer, Shift As Integer, x As Single, Y As Single)
9 l' X6 l4 ~% B! V/ w7 T2 \0 }" J
    Label1 = ""
' i( N" @5 ~  H4 p8 ]    Label2 = ""
, C" U2 G+ d' F) L) M2 S. ~- {3 M0 ^$ r, Y2 J9 l% n! m
End Sub6 R4 K% d9 ^& M3 b- Q0 a

' B6 K! [4 v9 i6 H/ `! y. \' hPrivate Sub Command1_Click()3 H& y5 Q' N! H7 R" j7 D# N
    6 B0 b' I, ^0 x: ?; D4 d
    Label1 = GetCpuName() & " CPU"0 ?0 S$ G% x) k- Y5 H0 T
    Label2 = "You have a" & IIf(InStr("AEIOU", Left$(Label1, 1)), "n", "")& J1 P! W! \8 `. y( B7 w; B" `

  o+ d1 s2 a" G1 P5 g, O' EEnd Sub: q* U; B9 S+ u8 F# S
------------------------------end---------------------------------  o( O4 _; K- ]0 b$ O
1 t, }: a( I, u( c( b

. z% N; X" q4 w* Q- m- k
, T# k3 w) p9 d* W
# Q6 o, _7 w8 e/ \3 ^& d- f4 k  n9 |' c# B1 [4 t, [: J
下面是modu1e.bas的源代码  v. r) i  z* @$ V7 A# |1 Y

* W: _" ?$ m! b( o9 ?9 k----------------------module1.bas的源文件--------------------------
  S- P+ r9 Q* r. @; m; ^1 iOption Explicit; X( v8 ?8 Y5 [+ I8 D. _5 j
'
/ H; ^# o. _% n: T- X4 D* H( E7 {" O'This shows how to incorporate machine code into VB8 A" A$ s9 g; ^
'''''''''''''''''''''''''''''''''''''''''''''''''''  o) j# ^8 E7 n! Y8 ~8 F  w% s
'The example fills the array with a few machine instructions and then copies5 H, {  i5 I6 k1 R
'them to a procedure address. The modified procedure is then called thru+ @" X! E9 g3 U: h% l
'CallWindowProc. The result of this specific machine code is your CPU Vendor Name.  h  w# G# _. f; O# E9 G1 y
'( S6 V6 k, r8 x( b9 G- l
'##########################################################################
) a; a. Y/ d. I7 @4 v0 F) n'Apparently it gets a Stack Pointer Error, but I don't know why; if anybody( [8 I" [9 B3 Y5 L" N" d
'can fix that please let me know...                          UMGEDV@AOL.COM' c8 o- M9 `/ s0 q) j. m. |
'The Error is not present in the native compiled version; so I think it got
5 i) @* p3 W& G$ ]' U% U+ ['something to do with the P-Code Calling Convention (strange though)...
6 H  _" e4 X9 _) k& n'##########################################################################
) m$ b- k5 X1 v1 x'
: H# \7 t+ H: U& ['Sub Dummy serves to reserve some space to copy the machine instructions into.
' t4 m; P; J. C0 X2 o: P'2 r* W7 U1 C; m& c% [$ L: T3 \7 b
'+ S1 k0 V$ n- Y, ]% ?/ `+ V
'Tested on Intel and AMD CPU's (uncompiled and compiled)
% g+ O2 f; V: _0 f2 A'! S1 f" q* Q, |8 i2 z9 k
'
* ~6 G: D0 e4 s' c! zPrivate 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
! i' }- j( \, e+ y+ uPrivate Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpvDest As Any, lpvSource As Any, ByVal cbCopy As Long)* g1 S) D- ^: z6 H' j: V4 k* L: p
Private x As Long
: P: d# [5 ^: e% y; z" Y1 m+ u/ s  }' N5 R7 E* _. t' ^
Public Function GetCpuName() As String) \. ?+ }1 J7 s  Y# \
  
; E0 m# G( B! L' Y0 V! r  Dim MachineCode(0 To 35)  As Byte
4 |- t& G# J, J+ `9 \' `  Dim VarAddr               As Long
( k, ]! V/ l4 u2 @  Dim FunctAddr             As Long7 m# e2 a% E! }6 h4 B9 q' r& n
  Dim EAX                   As Long- M* Y9 @7 e# h& w, d7 @
  Dim CPUName(1 To 12)      As Byte$ R& B3 ~, T' w/ g
  
1 ]! ~; c, f' R( B+ _  'set up machine code
3 w( M. |" U8 I' J5 G; K    ; F0 \/ T+ X! k8 h* w/ l  p; P
    MachineCode(0) = &H55    'push ebp
  V; C+ q0 X9 ~$ k6 ]8 b  v   
: r0 B" U: Z" g- z1 k    MachineCode(1) = &H8B    'move ebp,esp
2 p/ A) Z4 R/ b5 P( E$ ~    MachineCode(2) = &HEC8 }/ m' m( A" m2 t+ W- S
   
) E, T1 B( j- u# O! ?+ `' u    MachineCode(3) = &H57    'push edi5 Z- i" X; b: C
   
& C: ?$ M0 Y4 f) ?: a) C. G2 b    MachineCode(4) = &H52    'push edx
+ b9 ~4 k2 K* O3 A  U   
" f% v2 k$ d3 }; [: L5 t    MachineCode(5) = &H51    'push ecx
9 b% {6 y& l* C& {    . Z9 \/ Z- _* M
    MachineCode(6) = &H53    'push ebx
6 A, \3 s) q# j    : r5 t: ?& F  @9 q+ F( _
    MachineCode(7) = &H8B    'move eax,dword ptr [ebp+8]
9 ~- s9 D6 K  ]) ?    MachineCode(8) = &H45. N6 F5 y; I" H$ B: H
    MachineCode(9) = &H8
8 {& {6 g; u* F& D, o0 M   
" }% a* E3 R" Z+ P2 a    MachineCode(10) = &HF    'cpuid5 E' r5 V9 L% C7 t" b, N2 {
    MachineCode(11) = &HA25 ]! X" D! v* `! [" H+ K$ |4 a
    & j2 P  q7 b* i( |5 Z1 b7 p
    MachineCode(12) = &H8B   'mov edi,dword ptr [ebp+12]
4 M- Y6 n/ l6 L    MachineCode(13) = &H7D& T4 e- b7 H# q0 }: H
    MachineCode(14) = &HC
, d1 R1 P* e* w6 ~( {9 [    7 J4 Q4 l8 x9 K% A- L
    MachineCode(15) = &H89   'move dword ptr [edi],ebx/ [& m' ?3 U8 X, u" B7 w4 h  C% o
    MachineCode(16) = &H1F
8 V' R9 v4 Z) X; [    % g7 `& {. W5 Q0 d8 T
    MachineCode(17) = &H8B   'mov edi,dword ptr [ebp+16]; F) L+ O- ^+ ^
    MachineCode(18) = &H7D
% G/ K3 v& D, A' m- F0 u    MachineCode(19) = &H10; I' U, t9 Q6 C) }
    " l6 ]; @/ `1 w6 C
    MachineCode(20) = &H89   'move dword ptr [edi],ecx& y' A# r+ g+ S9 b
    MachineCode(21) = &HF
  f& i6 b7 y4 w9 V   
/ c. J, m! b1 q) Y5 [: y1 v    MachineCode(22) = &H8B   'mov edi,dword ptr [ebp+20]# ^( ?0 {! p; V1 |3 m- Y+ c& S
    MachineCode(23) = &H7D
, v7 j6 W# y: Z  [    MachineCode(24) = &H14( {/ _- X2 S/ W+ {7 }
    ! [: T" b1 r4 B4 L$ d
    MachineCode(25) = &H89   'move dword ptr [edi],edx
' ]; C( @* n6 L0 g2 [) ?    MachineCode(26) = &H179 S* V6 R& b, d4 G" C4 t
    9 ^0 j8 j8 a% T4 D
    MachineCode(27) = &H58   'pop ebx
& P. W/ n; K1 n2 G3 Y4 k# L$ @, s% s: B/ |- D6 E) U
    MachineCode(28) = &H59   'pop ecx2 D- Y' Y$ d5 }, U) v& u" k

' Y2 o- s& d* |2 y/ Q& |    MachineCode(29) = &H5A   'pop edx
: `  g. d. B4 k! |" [& }# I# l% ~* [8 I. N/ ?
    MachineCode(30) = &H55   'pop edi  p" @5 }% o* N3 V7 Z0 {& x
    5 A: f5 }' P- O5 U- ?. s/ Z
    MachineCode(31) = &HC9   'leave
& e4 x- p, U+ F, |' ?) y! _/ p2 K$ g% @8 e5 c
    MachineCode(32) = &HC2   'ret 16     I tried everything from 0 to 24
3 @+ c1 t. W% T4 q5 N    MachineCode(33) = &H10   '           but all produce the stack error
: V8 d2 d( h$ b/ Y    MachineCode(34) = &H0
  D8 K* B' N* _& c! S  s   
' G  |+ c2 {( z* y- F2 y9 a$ ?2 X    'tell cpuid what we want
, A1 |( l1 }9 Z' e% m/ D8 e, u- ~    EAX = 02 c. z. y, v9 u
    9 _% t( e$ H, N7 a% g' ?
    'get address of Machine Code0 g  ?! B! ^9 \; R) z
    VarAddr = VarPtr(MachineCode(0))* I4 |, d2 q6 ?6 i' {
    ( r" e$ \: p& T, ]& v/ a3 M& ?1 D
    'get address of Sub Dummy$ O! S5 t1 p; f+ \- e: n
    FunctAddr = GetAddress(AddressOf Dummy)  [; Z& ?& o; r  A% `: F& ?7 M
    $ C! _2 E+ Z4 v) b
    'copy the Machine Code to where it can be called
/ Z. G7 F; i0 I9 E6 N" u    CopyMemory ByVal FunctAddr, ByVal VarAddr, 35 '35 bytes machine code4 o. c3 N: u# h- M& d5 `1 o
   
% |* S7 H# o/ K    'call it% X! ]. B2 [& S
    On Error Resume Next 'apparently it gets a stack pointer error when in P-Code but i dont know why
' x/ _6 m) F" T; @1 k3 W& ?$ J5 n      CallWindowProc FunctAddr, EAX, VarPtr(CPUName(1)), VarPtr(CPUName(9)), VarPtr(CPUName(5))
& p% W5 p; Z* L+ j. \) @      'Debug.Print Err; Err.Description
  w. w3 S' T8 O, }      'MsgBox Err & Err.Description
2 D2 l  ~1 l3 T# M1 ~1 g% S$ Z    On Error GoTo 0
& K- e, c8 X* V3 K; k' J4 c# T   
: e9 ?# v* C& e' N! g" [* w    GetCpuName = StrConv(CPUName(), vbUnicode) 'UnicodeName5 q2 K. l, ^; ^2 t" T) ?9 H
   
6 M1 O+ ]3 N2 N3 i9 X% M# `# }End Function0 H( x3 Z/ l- ?6 S" }. s0 o
( G8 Z0 o% j+ A$ L1 x( }% P
Private Function GetAddress(Address As Long) As Long
" J' ~, a6 j% T# c) x8 a% o3 D! t) ?2 f/ a- W+ O
    GetAddress = Address
; B: ^8 E  l, {3 _: @/ _" K. X" ?$ T* k; v, H9 t- G; X3 U. }. u: \
End Function  d) N& m; D; E
2 @9 f( q$ S, O* T) k. X
Private Sub Dummy()
8 [2 l- ]- ~5 X
$ E+ ]" Z: ^7 `* U  'the code below just reserves some space to copy the machine code into
. D# D5 D! y. V- x3 }) s% i" h  'it is never executed
, n" {9 l, _" s" H$ C3 x% g  X" V& j. }6 [  L
    x = 06 `, p$ D! ~8 \# a) a6 h
    x = 1
$ X- N* |* {2 k0 B/ g2 P    x = 2
& ]" \: r" h; V& a  }4 Z    x = 3
2 i& _; a/ s) ?/ ~! a" `+ b    x = 4
; d2 D+ U) m: Z9 d7 @6 S" E% x    x = 5
- d5 F* z. N2 N# Q" L  J8 M    x = 6. O, N; y3 Y& H; s7 x
    x = 7& N3 z0 D" O; t0 }. d
    x = 8/ H" ?7 n, r1 w, m" |5 d
    x = 9, E4 V; H) n* E, w
    x = 108 n/ y. S* u! V0 N: p4 k
    x = 0' y2 }) D0 i. h( V+ N
    x = 1) i5 v0 [$ m/ H
    x = 2
* [2 K* q# ]" I# {# y    x = 3
5 u: k* ]* _& m# w- X    x = 4- }% Z1 M1 w  P0 E+ x7 L) }
    x = 5
7 C+ m1 f( A1 M9 K    x = 6. b) P4 B6 R( ^8 [, [- O3 J
    x = 7
. V4 f( Q9 q. ^/ w9 |' {2 \    x = 8
, E5 P% F; R+ U* Z    x = 9$ p2 ?9 Q  @  n3 `. B; S' K
    x = 10
. z+ P1 B/ x/ q) \   
# S8 }% M5 I' N1 W2 x( WEnd Sub
+ W9 i/ D# @! L9 V; _------------------------------end--------------------------------------
- }1 S/ i3 {1 |4 `
' I, o% A* U( }+ D1 H7 O( A- q 9 @. q( r: n4 a( O. F

+ G" P" y7 |% _) u1 V. F

本版积分规则

关闭

下沙大学生网推荐上一条 /1 下一条

快速回复 返回顶部 返回列表