Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Problem passing strings between VBScript/VBAapp and Win32 API

358 views
Skip to first unread message

PackRat

unread,
Feb 1, 2001, 1:25:53 PM2/1/01
to
How do I *reliably* pass the memory location (address) of a string
between VBScript (and VBA) and Win32 API functions/subs?


PART ONE

In other words, what I'm looking for is sort of like an "address-of"
function for string variables.

From my reading (mostly from "Win32 API programming with Visual Basic"
by Steven Roman, O'Reilly, 2000) I'm aware that VB has two undocumented
(and thus unsupported) holdovers from earlier roots, namely, VarPtr and
StrPtr. I've read that VB string variables do not contain the value of
a string but, rather, *point* to the contents of a string. Thus,
VarPtr(strname) gives the address of the strname pointer, and
StrPtr(strname) gives the address of the contents of the strname string
(which also the value contained at the address of the strname pointer):

addr bbbb
v
,-----,-------------------------------,
| Len | strname's Unicode contents\00 |
'-----'-------------------------------'
^
addr aaaa |
v |
,------, |
| bbbb |----------'
'------'
strname
variable

Then, VarPtr(strname) = aaaa and StrPtr(strname) = bbbb. There are
some other complications, but that's the basic idea.

Since VarPtr and StrPtr are not officially supported, is there any other
way that aaaa and bbbb can be derived from strname ?


PART TWO

Using VB CCE (Common Control Edition), I've created an .ocx file that
has the following contents: (names: form="wndw", control="tools")

=====
Private Declare Function CopyMemory Lib "kernel32" Alias _
"RtlMoveMemory" (lpDest As Any, lpSource As Any, _
ByVal cbCopy As Long)

Public Function vPtr(ByVal varname As String) As Long
vPtr = VarPtr(varname)
End Function

Public Function sPtr(ByVal varname As String) As Long
sPtr = StrPtr(varname)
End Function

Public Sub CopyMem(dest As Long, src As Long, ByVal bytecount As Long)
CopyMemory dest, src, bytecount
End Sub
=====

In a VBScript file, for example, I can reference the above .ocx by the
name "wndw.tools". Here are the basic script elements (ignore the
bracketed "ByVal" keywords):

=====
1 Set tool = CreateObject("wndw.tools")
2 s = "help"
3 sp = tool.sPtr(s)
4 vp = tool.vPtr(s)
5 MsgBox "StrPtr = " & sp & Chr(10) & "VarPtr = " & vp
6 CopyMem lng, [ByVal] vp, 4
7 MsgBox "lng = sp ? " & (lng = sp)
8 CopyMem ct, [ByVal] sp-4, 4
9 MsgBox "Length of contents of s = " & ct
10 b = String(10,0)
11 CopyMem b, [ByVal] sp, 10
12 msg = ""
13 For i = 1 To 10
14 If Mid(b,i,1) = Chr(0) Then
15 msg = msg & "0 "
16 Else
17 msg = msg & Asc(Mid(b,i,1)) & " "
18 End If
19 Next
=====

Line 1 sets up the connection with the .ocx (and thus with VB functions
and with the Win32 API). Lines 2-5 get the StrPtr and VarPtr values.
Lines 6-7 verify that the content of the strname variable is indeed the
same as StrPtr (the address of strname's string contents). Lines 8-9
verify that strname's contents are in Unicode format (2 bytes for each
of the four characters in "help" plus 2 bytes of terminating zeros, for
a total of 10 bytes). Lines 10-19 display the values of the 10 bytes of
strname's Unicode contents.

The MsgBox's are supposed to display the following messages:

StrPtr = bbbb
VarPtr = aaaa
lng = sp ? True
Length of contents of s = 10
104 0 101 0 108 0 112 0 0 0

The problem seems to lie with the fact that in VB the pointers need to
be "ByVal" arguments in lines 6, 8, and 11, but VBScript doesn't permit
"ByVal". I've tried all sorts of variations in the .ocx declarations
and also using CLng(vp) in the script, but to no avail--no matter what I
do, I get a "type mismatch" error at the beginning of line 6 (I presume
the same error would occur at lines 8 and 11 as well).

How can I get the above VBScript code to execute correctly? I realize
that the .ocx may need slight revision as well. (I need to be able to
do this in order to access and manipulate text in an edit control in
reply emails using the Novell GroupWise Object API.)

Thanks in advance for any help anyone can give!

PackRat

Tore

unread,
Feb 2, 2001, 3:08:52 AM2/2/01
to
I'm not sure what you are trying to do - but are you sure you aren't making
it overly complex?

You typically only need to worry about the pointer when interfacing with a
very few "difficult" API's - usually not ones you'd deal with from VBScript.

HTH,
Tore.


"PackRat" <pac...@anet-chi.com> wrote in message
news:e4rh7toehcqltofh7...@4ax.com...

PackRat

unread,
Feb 2, 2001, 10:04:36 AM2/2/01
to
"Tore" <tbos...@iname.com> wrote:
>I'm not sure what you are trying to do - but are you sure you aren't making
>it overly complex?
>
>You typically only need to worry about the pointer when interfacing with a
>very few "difficult" API's - usually not ones you'd deal with from VBScript.

Besides learning better in general how to deal with passing string
pointers and data to and from Win32 APIs, what I'm specifically trying
to do is to get text data from an edit window, reformat it via some
scripted functions I've written, and put it back into the edit window.

I'm experimenting with two different approaches:

(1) lc = SendMessageByString( hWnd, EM_GETLINE, linetoget, buffer )

where linetoget is a line number in the edit window and buffer is
the string where the contents of the line are to be copied; buffer's
first two characters are the binary length of the line. This approach
crashes the script engine every time I reach the code above (which is
standard and found in many books) with a Windows error that WScript has
caused an "illegal operation" in user.exe, probably because the address
of buffer is not being correctly handled.

(2) CopyMem destaddr, srcaddr, [ByVal] numbytes

where ByVal would appear in standard VB/VBA but not in VBScript, which
is what I'm trying to use. Supposedly using (numbytes) is the
equivalent of ByVal (it's ByRef without the parentheses). CopyMem is a
function that is but a public function envelope for the CopyMemory API
call (also known as RtlMoveMemory) in a self-written .ocx file.
destaddr and srcaddr are both string addresses (pointers) in this
particular use, and that's where the problem arises: the VBScript fails
at the line above with a "type mismatch" error no matter what I've
tried. That's why I tried to give as much detail as possible in my
previous post.

I hope this gives a clearer indication of where I'm at and what I'm
trying to accomplish.

PackRat

Tore

unread,
Feb 2, 2001, 10:47:02 AM2/2/01
to
Your approach #1 is the recommended approach. Make sure you have
initialized the buffer to an appropriate length before sending the
EM_GETLINE message:

Declare Function SendMessageByString Lib "user32" _
Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, _
ByVal wParam As Long, ByVal lParam As String) As Long

buffer = String(0, 255)


lc = SendMessageByString( hWnd, EM_GETLINE, linetoget, buffer )

From the SDK documentation:

lParam
Pointer to the buffer that receives a copy of the line. Before sending the
message, set the first word of this buffer to the size, in TCHARs, of the
buffer. The size in the first word is overwritten by the copied line.

HTH,
Tore.


"PackRat" <pac...@anet-chi.com> wrote in message

news:kghl7tgh8rqfodgm9...@4ax.com...

PackRat

unread,
Feb 4, 2001, 10:37:12 PM2/4/01
to
"Tore" <tbos...@iname.com> wrote:
>Your approach #1 is the recommended approach. Make sure you have
>initialized the buffer to an appropriate length before sending the
>EM_GETLINE message:
>
>Declare Function SendMessageByString Lib "user32" _
> Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, _
> ByVal wParam As Long, ByVal lParam As String) As Long
>
>buffer = String(0, 255)
>lc = SendMessageByString( hWnd, EM_GETLINE, linetoget, buffer )
>
>From the SDK documentation:
>
>lParam
>Pointer to the buffer that receives a copy of the line. Before sending the
>message, set the first word of this buffer to the size, in TCHARs, of the
>buffer. The size in the first word is overwritten by the copied line.

BTW: you meant "buffer = String(255, 0)" rather than "(0, 255)", didn't
you??

I've already tried what you suggested. I think the problem lies more in
*passing* values to both "linetoget" and "buffer" in the
SendMessageByString API call. VBScript deals in "variants" and
SendMessageByString wants a "ByVal" long and string. Books about
VBScript indicate that putting parentheses around a variant argument to
an external/object function call in VBScript forces it to pass the value
"ByVal" rather than "ByRef", but I haven't had success getting that to
work. As implied in my original post, there are several layers involved
in passing function argument values:


WinAPI function
^ |
| v
self-written function in .ocx which calls WinAPI function
^ |
| v
VBScript call to self-written function in .ocx


Additionally, my original query also asked about whether there are any
other ways to get pointer values of variables besides VarPtr and StrPtr,
since these are not supported by MS and are not guaranteed to appear in
future versions of VB.

Any further suggestions?


PackRat

Randy Birch

unread,
Feb 4, 2001, 10:43:06 PM2/4/01
to
: other ways to get pointer values of variables besides VarPtr and StrPtr,

: since these are not supported by MS and are not guaranteed to appear in
: future versions of VB.


They are no longer in vb.net.

--

Randy Birch
MVP Visual Basic

Take the vb.net poll at:
http://www.mvps.org/vbnet/
http://www.mvps.org/ccrp/

Please respond only to the newsgroups so all can benefit.

Tore

unread,
Feb 5, 2001, 12:45:49 AM2/5/01
to
I think maybe I am confused as to what problem you have where (and you may
be, too).

If I understand correctly, you are trying to access your own OCX from
VBScript, and you are trying to access an Edit Control (text box) in another
app from your OCX, resulting in the VBScript obtaining a line of text from
the edit control. Looking back at your original code it looks like you are
trying to copy data from a buffer in the OCX to a variable in VBScript?
Don't.

Do it the way you are supposed to: Allow COM to provide the data passing
between your OCX and VBScript - both ways. That is simple, easy, and does
not require you to jump any hoops. Use normal API calling conventions for
obtaining the text line in your OCX. Forget about CopyMemory for now - it
isn't going to help you with this particular API or problem.

If you are learning VB (or any MS technology) - go with the flow. Try to
find out the recommended way of doing things. It makes everything a lot
easier. And just because CopyMemory is available, that doesn't mean you
should use it. There are a few (very few) cases where it is required for
interfacing with certain API's, but this is not one of them. When you come
across such a case, you'll be best off finding a sample that already handles
that particular API.

You are not supposed to worry about pointers in VB - hence there are no
other pointer functions available than the two mentioned.

HTH,
Tore.


"PackRat" <pac...@anet-chi.com> wrote in message

news:ii6s7tspqdoq1vd4k...@4ax.com...

Tore

unread,
Feb 7, 2001, 1:52:22 PM2/7/01
to
I was a little too rash in my treatment of EM_GETLINE (I don't use it).

EM_GETLINE is a little tricky - it requires that the buffer contains the
number of bytes allowed (maximum buffer size) as the first two bytes. In
order to use a string for this, you have to use CopyMemory in order to set
the buffer length. However, you can use a byte array instead, in which case
you can set the buffer size as follows (observe proper API declaration):

caLine(0) = Chr$(UBound(caLine) And &HFF)
caLine(1) = Chr$((UBound(caLine) And &hFF00) \ &HFF)

(The "And &hFF00" is to avoid overflow in case your array is more than 64k
in size - not supported). You cannot simply concatenate the two characters
in a string, because VB strings are Unicode (16-bit characters).

However, I would recommend using WM_GETTEXT instead of EM_GETLINE. It
returns the entire content of the control's window (see SDK docn for
details), and works on several window types.

You can use the Split function on the result (available in VB6 and VBScript
version 2) to obtain individual lines.

Also, move your logic from the VBScript to your component - use a dumb
script and a smart control, rather than the other way around.

The following works (I deleted unneccessary code):

** ActiveX Component:

Option Explicit

Private Declare Function FindWindow Lib "user32" Alias _
"FindWindowA" (ByVal lpClassName As String, ByVal _
lpWindowName As String) As Long
Private Declare Function GetDlgItem Lib "user32" (ByVal _
hWnd As Long, ByVal wID As Long) As Long
Private Declare Function SendMessageByString Lib "user32" _
Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg _
As Long, ByVal wParam As Long, ByVal lParam As String) _
As Long

'# Change Start - 2/7/2001 - Tore Bostrup:
Private Declare Function SendMessage Lib "user32" _
Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg _
As Long, ByVal wParam As Long, lParam As Any) _
As Long
Private Const WM_ACTIVATE = &H6
Private Const WM_GETTEXT = &HD
Private Const WM_GETTEXTLENGTH = &HE
'# Change End

Public Function GetHwndFromClass(ByVal classname As String) _
As Long
GetHwndFromClass = FindWindow(classname, vbNullString)
End Function

Public Function GetHwndFromParentAndWndID(ByVal handle As Long, _
ByVal wID As Long)
GetHwndFromParentAndWndID = GetDlgItem(handle, wID)
End Function

'# Change Start - 2/7/2001 - Tore Bostrup
'# New Function
Public Function GetText(ByVal hWndParent As Long, _
ByVal hWnd As Long) As String

Dim sBuf As String
Dim lCharsReturned As Long
Dim lMaxBuf As Long
Dim lRet As Long

lRet = SendMessage(hWndParent, WM_ACTIVATE, 0, 0&)
DoEvents

lMaxBuf = 10240
sBuf = String$(lMaxBuf, vbNullChar)
lCharsReturned = SendMessageByString( _
hWnd, WM_GETTEXT, lMaxBuf, sBuf)
DoEvents
Debug.Print Hex$(hWndParent), Hex$(hWnd), lRet, lMaxBuf, lCharsReturned
GetText = Left$(sBuf, lCharsReturned)

End Function
'# Change End

======================================================

** VBScript:

Option Explicit

Dim handle
Dim handle2
Dim TextBuff
Dim tool
'


Set tool = CreateObject("wndw.tools")

'
handle = tool.GetHwndFromClass("Notepad")
If handle = 0 Then
MsgBox "Currently, no Notepad window open!"
Else
handle2 = tool.GetHwndFromParentAndWndID( handle, 15 ) ' 15 is the _
'window ID of the Notepad edit window
TextBuff = tool.GetText(handle, handle2)
MsgBox "GetText: '" & TextBuff & "'"
End If


HTH,
Tore.

PackRat <pac...@anet-chi.com> wrote in message

news:7bp18tc223v0c67qb...@4ax.com...
> In response to my previous message:

> Let me explain exactly what I'm trying to do. The organization I work
> for has now standardized on Novell GroupWise for email, and I can no
> longer use another Windows email client (such as Pegasus Mail). In my
> opinion, there are several deficiencies in GroupWise, compared with
> other well known email clients. One of the things that GroupWise is
> crappiest with is quotation of the original message within a reply.
> What I'd like to do is write a VBScript (and associated .ocx's to access
> the WinAPI and the GroupWise Object API) that will get GroupWise's
> quotation and replace it with a reformatted quotation, each line of
> which begins with a quotation character.
>
> Using SendMessage, I'm able to (correctly) get the number of lines in
> the edit control and how long each line is in turn when obtained in a
> loop. However, I seem unable to get the actual *contents* of each line
> itself. WScript crashes every time it reaches that VBScript/.ocx
> SendMessage statement. Here are the two sets of code I'm testing with.
> The first is the source for the .ocx file, and the second is the
> VBScript file. Something must be wrong in the parameter passing, but I
> can't seem to figure it out. If you (or anyone else) can, I would
> certainly appreciate it!
>
> (I substituted the Notepad edit control for the GroupWise edit control.
> Otherwise, the code is identical to what I'm using to test with
> GroupWise itself. Before running this code, there should be a Notepad
> window open containing text.)
>
> ==============================================================
>
> 'VB code in .ocx file (using VB5 CCE):
> ' [projectname=wndw, controlname=tools]
>
> Private Declare Function FindWindow Lib "user32" Alias _
> "FindWindowA" (ByVal lpClassName As String, ByVal _
> lpWindowName As String) As Long
> Private Declare Function GetDlgItem Lib "user32" (ByVal _
> hWnd As Long, ByVal wID As Long) As Long
> Private Declare Function SendMessageByNum Lib "user32" _
> Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg _
> As Long, ByVal wParam As Long, ByVal lParam As Long) _
> As Long
> Private Declare Function SendMessageByString Lib "user32" _
> Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg _
> As Long, ByVal wParam As Long, ByVal lParam As String) _
> As Long
>
> Public Function GetHwndFromClass(ByVal classname As String) _
> As Long
> GetHwndFromClass = FindWindow(classname, vbNullString)
> End Function
>
> Public Function GetHwndFromParentAndWndID(ByVal handle As Long, _
> ByVal wID As Long)
> GetHwndFromParentAndWndID = GetDlgItem(handle, wID)
> End Function


>
> Public Function vPtr(ByVal varname As String) As Long
> vPtr = VarPtr(varname)
> End Function
>
> Public Function sPtr(ByVal varname As String) As Long
> sPtr = StrPtr(varname)
> End Function
>

> Public Function SendMsgByNum(ByVal hWnd As Long, ByVal wMsg _
> As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
> SendMsgByNum = SendMessageByNum(hWnd, wMsg, wParam, lParam)
> End Function
>
> Public Function SendMsgByString(ByVal hWnd As Long, ByVal wMsg _
> As Long, ByVal wParam As Long, ByVal lParam As String) As Long
> SendMsgByString = SendMessageByString(hWnd, wMsg, wParam, lParam)
> End Function
>
> ==================================================================
>
> 'VBScript code:
>
> Option Explicit
>
> Const EM_GETLINECOUNT = &HBA
> Const EM_LINEINDEX = &HBB
> Const EM_LINELENGTH = &HC1
> Const EM_GETLINE = &HC4
>
> Dim handle
> Dim handle2
> Dim msg
> Dim lin
> Dim p
> Dim LineCount
> Dim TextLen
> Dim TextBuff
> Dim tmpbuff
> Dim sp
> Dim vp
> Dim tool
> '


> Set tool = CreateObject("wndw.tools")

> '
> handle = tool.GetHwndFromClass("Notepad")
> If handle = 0 Then
> MsgBox "Currently, no Notepad window open!"
> Else
> handle2 = tool.GetHwndFromParentAndWndID( handle, 15 ) ' 15 is the _
> window ID of the Notepad edit window
> LineCount = tool.SendMsgByNum( handle2, EM_GETLINECOUNT, 0, 0)
> TextBuff = ""
> For lin = 0 To 4 'for testing purposes--orig: To LineCount - 1
> p = tool.SendMsgByNum(handle2, EM_LINEINDEX, lin, 0)
> TextLen = tool.SendMsgByNum( handle2, EM_LINELENGTH, p, 0) + 1
> tmpbuff = Chr(TextLen And &HFF) & Chr(TextLen \ &H100)
> tmpbuff = tmpbuff & String(255, 0)
> sp = tool.sPtr(tmpbuff) 'for testing purposes
> vp = tool.vPtr(tmpbuff) ' " "
> ' WScript crashes on the next statement (or within its equivalent
> ' in the .ocx file)
> TextLen = tool.SendMsgByString(handle, EM_GETLINE, lin, (tmpbuff))
> TextBuff = TextBuff & Mid(tmpbuff, 3) & vbCr
> Next
> MsgBox "'" & TextBuff & "'"
> End If
>
> =======================================================================
>
> I used parentheses around tmpbuff in the GETLINE statement because
> that fourth parameter is supposed to be "ByVal" rather than "ByRef".
> But it seems to crash WScript either way!
>
> By the way, when I say "crash" in the paragraphs above, I mean it
> displays the message "WScript caused an illegal operation in
> User.exe..."
>
> As I said, I think the problem may lie somewhere in the parameter
> passing among the several layers, but, then again, it may be something
> completely different.


>
> >You are not supposed to worry about pointers in VB - hence there are no
> >other pointer functions available than the two mentioned.
>

> A description of VB.Net that I recently read very pointedly stated that
> the next version of Visual Basic was written from the ground up to be
> compatible with C++, etc., and that it therefore does not contain
> VarPtr, StrPtr, or ObjPtr (or the related array pointers).
>
> I hope you (or anyone) can give some guidance on how to make this work
> correctly--thanks in advance!
>
> PackRat
>


0 new messages