View Full Version : Using thincore.dll with Visual Basic 6.0
Joe Caverly
20-11-2023, 17:40
I would like to use thincore.dll with Visual Basic 6.0
I looked in the \thinBasic\sdk\sdk.zip,
and found thinBasic BASIC SDK\PB,
which I could use as a reference for embedding in VB6.
Before I do so,
I was wondering if anyone has already created a thinBasic SDK for VB6,
and would be interested in sharing it.
My end goal is to create a COM DLL,
which I can use with Visual Basic 6.0,
Visual FoxPro 9.0,
and other COM-callable languages.
I occasionally use AutoIt, which comes with AutoItX, a DLL/COM control.
Add AutoIt features to your favorite programming and scripting languages!
Also features a C# assembly and PowerShell CmdLets.
Perhaps a future addition to thinBasic could be something similar,
maybe a thinBasicX COM DLL,
which is what I am hoping to do with VB6 and thincore.dll
Regards and Thanks,
Joe
ErosOlmi
21-11-2023, 08:46
Hi Joe,
thanks for your suggestion, I will check what I can do.
thinBasic Core engine is written using Power Basic compiler and should definitely possible to develop COM components using it.
Eros
Joe Caverly
22-11-2023, 21:47
I'm having issues in getting thinCore.dll working with Visual Basic 6.0
Option Explicit
' Microsoft Visual Basic 6.0 (SP6)
' Windows 10 [Version 10.0.19045.3693] 22H2
'
' AddIn Used - Visual Basic 6 IDE Linker Addin
' - LinkSwitches /SUBSYSTEM:CONSOLE
' Ref: https://www.vbforums.com/showthread.php?866321-VB6-IDE-Linker-AddIn
'
' Ref: https://github.com/ErosOlmi/ThinBASIC_On_GitHub/blob/master/Lib/thinCore.INC
' thinCore.dll is in my App.Path folder
Declare Function thinBasic_Init Lib "thinCore.dll" (ByVal hWnd As Long, _
ByVal cInstance As Long, _
ByVal sKey As String) As Long
Declare Function thinBasic_Release Lib "thinCore.dll" (ByVal hScript As Long) As Long
Declare Function thinBasic_Run Lib "thinCore.dll" (ByVal hScript As Long, _
ByVal sBuffer As String, _
ByVal BufferType As Long, _
Optional ByVal Options As Long, _
Optional ByVal DebugMode As Long, _
Optional ByVal LogMode As Long, _
Optional ByVal ObfuscateMode As Long, _
Optional ByVal CallingProgram As Long, _
Optional ByVal DependancyMode As Long) As Long
Dim Con As New Console
Dim hScript As Long
Dim sScript As String
Dim hRun As Long
Const thinBasic_BufferType_IsFile = 0
Sub Main()
On Error GoTo CatchError
sScript = "E:\Documents\vb6\ThinBasic\Alert.tBasic"
Con.OutStd ("App.hInstance = " + Str$(App.hInstance))
Con.OutStd ("App.Path = " + App.Path)
Con.OutStd ("Init")
hScript = thinBasic_Init(0, App.hInstance, "")
Con.OutStd ("Run")
hRun = thinBasic_Run(hScript, sScript, thinBasic_BufferType_IsFile, 1 Or 2, False, False, False, 1, False)
'Program quits here
'From IDE: Run-time error '0'
'From EXE: No error, Alert.tBasic is not run
'
'Output:
'App.hInstance = 4194304
'App.Path = E:\Documents\vb6\ThinBasic
'Init
'Run
Con.OutStd ("Release")
thinBasic_Release (hScript)
Exit Sub
CatchError:
Con.OutStd (Err.Number)
Resume Next
Return
End Sub
The program quits when thinBasic_Run is called.
I have probably missed something in the translation of the Declare functions.
Constructive assistance would be appreciated.
Joe
ErosOlmi
16-03-2024, 11:43
Sorry Joe, I forgot about this thread.
If you change
thinBasic_Init(0, App.hInstance, "")
to
thinBasic_Init(0, App.hInstance, "thinbasic")
should work
But there are other problems if you try to execute your script again using current thinCore.dll
I'm making some fix to:
thinBasic_Init
thinBasic_Run
thinBasic_Release
in order to make it working as an engine
Attached a VB6 example with an update thinCore.dll that works better but still some problems.
I will work on this next days and will be back.
Joe Caverly
17-03-2024, 01:47
Thanks Eros,
Your example works as described.
I'm now trying to figure out how to modify a variable from VB6.
For example;
Dim sScript As String
Dim hRun As Long
Dim test As Long
test = 1957
Const thinBasic_BufferType_IsFile = 0
Const thinBasic_BufferType_IsScript = 1
On Error GoTo CatchError
sScript = txt_thinBasicSourceCode.Text
If Len(sScript) Then
hScript = thinBasic_Init(0, App.hInstance, "thinbasic")
If hScript = 0 Then
hRun = thinBasic_Run(hScript, sScript, thinBasic_BufferType_IsScript, 1 Or 2, False, False, False, 1, False)
'thinBasic_Release (hScript)
End If
Debug.Print thinBasic_VariableExists("test")
Debug.Print test
Else
MsgBox "Please type some thinBasic code into textbox"
End If
Note I have created a Long variable called "test",
and assigned a value of 1957.
thinBasic_VariableExists("test") returns 1 if the variable exists, which it does.
In the text box, if I add;
long Test = 1960
sMsg += Str(Test)
...before the MsgBox 0, sMsg, 1960 is returned in the MsgBox.
The help file has a blank page for thinBasic_VariableExists, along with all of the other thinBasic_ functions.
I was just guessing what the thinBasic_ functions do,
but not being very successful.
I did a review of \thinBasic\Lib\thincore.inc,
but still having issues in understanding.
How would I return the test variable,
with a value of 1960, to VB6?
Joe
Joe Caverly
17-03-2024, 17:16
After a restful sleep, I've done some more research.
I'm thinking that I have to use thinBasic_LoadSymbol
I've declared it in VB6 as follows;
Declare Function thinBasic_LoadSymbol Lib "thinCore.DLL" (ByVal SymbolName As String, ByVal ReturnCode As Long, ByVal FunctionOrSubPointer As Long, Optional ByVal ForceOverWrite As Long) As Long
So, if I want to use thinBasic to increment a number from VB6 by 1,
in VB6 the flow would go something like this...
thinBasic_LoadSymbol "VB6AddOne", thinBasic_ReturnNumber, VarPtr(TBAddOne(20))
VB6AddOne will be my new "keyword" (function) that I call in VB6.
TBAddOne will be my function in thinBasic.
I pass the number 20 in TBAddOne,
which will increment by 1,
and return 21.
CODEPTR is not recognized by VB6,
so I am using VarPtr.
Not sure if this is the proper replacement. :confused:
In the text box,
I add the following function for thinBasic;
function TBAddOne(theTest) as long
function = theTest + 1
end function
As shown in attachment, I've got issues. ;--)
10357
Constructive guidance would be appreciated.
Joe
ErosOlmi
18-03-2024, 08:30
Hi Joe,
will prepare an example next days.
In the meantime refer to thinCore.inc file here https://github.com/ThinBASIC/module_core/blob/master/thinCore.inc that shows thinCore.dll exported functionalities you can use.
thinBasic_LoadSymbol is used to add new keywords inside thinBasic. You need to have a compiled Sub/Function an map it in thinBasic passing its Sub/Function pointer.
Then you will be responsible to parse thinBasic source code. This is a little complex but I can show you next days
I do not know if VB6 has the possibility to have a pointer to a Sub/Function like CodePtr
Anyway, to add a new variable use thinBasic_AddVariable
You can just create a variable initializing it value and also create a variable that uses a memory area of your own VB6 variable passing optional parameter VarMemPtr
Example for numeric (%VarSubType_Long = 5, refer to https://github.com/ThinBASIC/module_core/blob/master/thinCore.inc )
call this before thinBasic_Run to add a variable of type LONG called MyLog with value 1234
thinBasic_AddVariable("MyLong", "", 1234, %VarSubType_Long)
call this before thinBasic_Run to add a variable of type LONG called MyLog that share the same memory area of your VB6 MyLongInVB6 LONG variable
Dim MyLongInVB6 as long
thinBasic_AddVariable("MyLong", "", 0, %VarSubType_Long, VarPtr(MyLongInVB6 ))
ReneMiner
18-03-2024, 14:44
Just as a hint: put an invisible (OUT OF VISIBLE RANGE ONLY) Textbox on your vb-form. Save the hwnd of it simply as Hex$ for a filename in an empty subfolder of your project. From thinbasic send
Dword Htext =val("0x" & SHELL_CAPTUREOUTPUT("CMD /C DIR /A:-D /B " & app_scriptpath & "the_folder\*.*", "", %Sw_hide,10))
Since its from same process you can use STRING sNUMERICS = mkbyt$(49,00,57,00,53,00,55,00,00)
Thats "1957" in widechar with a terminating zero
Then sendmessage(htext, %em_settext, sNumerics,-1)
No more sure if it was -1 but it should do something as redraw or refresh the control.
In vb your form should have a sub textbox1_textchange() that should fire up. Use val(textbox1.text) ...
ErosOlmi
18-03-2024, 22:30
Here attached a VB6 project in which I've injected a thinBasic variable connected to a VB6 variable so calling VB program can share variables with thinBasic script at runtime.
The script evaluate a math expression over X with X from a min to a max with step
ATTENTION: I've created a new thinCore.dll version for this script.
There is a a new exported function called thinBasic_AddVariable_VB
I did this because most of thinBasic API interfaces use EXTENDED numeric data type and EXTENDED (10 bytes) are not supported in VB6
So I developed thinBasic_AddVariable_VB that accepts Doubles
Hope this can help.
Joe Caverly
18-03-2024, 23:46
Thanks Eros!
I've tried your sample out,
and it works as documented.
I will do some more testing over the next few days.
Joe
ReneMiner
19-03-2024, 12:29
ATTENTION: I've created a new thinCore.dll version for this script.
....
I did this because most of thinBasic API interfaces use EXTENDED numeric data type and EXTENDED (10 bytes) are not supported in VB.
Not quite. Microsoft hides it but for backward compatibility to 16 bit they kept the datatype - also its rounded up to use 3x4 bytes in memory but actually it calculates as real10 but is named Longdouble. There are some Api-functions to it (search "LDOUBLE")
ReneMiner
19-03-2024, 13:39
Ldbl only. Not that anyone could detect it
Joe Caverly
23-03-2024, 14:22
Example VB6 code of how to use VB6 variables from a thinBasic Script.
Attribute VB_Name = "mod_Main"
Option Explicit
Sub Main()
Dim hScript As Long 'handle to thinBasic Script
Dim sScript As String 'thinBasic Script
Dim hRun As Long 'thinBasic_Run
Dim x As Double 'Declare variables
Dim y As Double 'to be
Dim Amount As Double 'used in thinBasic Script
Dim lRet As Long 'thinBasic_AddVariable_VB
Dim sResult As String 'thinBasic Script Output
Const thinBasic_BufferType_IsFile = 0
Const thinBasic_BufferType_IsScript = 1
On Error GoTo CatchError
x = Val(Right$(Time$, 2)) * 0.01
y = 0
Amount = 0
'Begin thinBasic Script
sScript = "Amount = 140.97" + vbCrLf
sScript = sScript + "y = x + Amount"
'End thinBasic Script
If Len(sScript) Then
hScript = thinBasic_Init(0, App.hInstance, "thinbasic")
If hScript = 0 Then
lRet = thinBasic_AddVariable_VB("x", "", 0, VarSubType_Double, VarPtr(x))
lRet = thinBasic_AddVariable_VB("y", "", 0, VarSubType_Double, VarPtr(y))
lRet = thinBasic_AddVariable_VB("Amount", "", 0, VarSubType_Double, VarPtr(Amount))
hRun = thinBasic_Run(hScript, sScript, thinBasic_BufferType_IsScript, 1 Or 2, False, False, False, 1, False)
sResult = sResult + Time$ + " : "
sResult = sResult + "y=" + Format$(y, "####.00") + " : x=" + Format$(x, "####.00")
sResult = sResult + " : Amount=" + Format$(Amount, "####.00") + vbCrLf
Debug.Print sScript
Debug.Print sResult
thinBasic_Release (hScript)
End If
Else
Debug.Print "Where's the code for the thinBasic Script?"
End If
Exit Sub
CatchError:
MsgBox "Error occurred: " + Err.Description
Resume Next
Return
End Sub
Attribute VB_Name = "mod_thinBasic"
' Ref: https://github.com/ErosOlmi/ThinBASIC_On_GitHub/blob/master/Lib/thinCore.INC
' thinCore.dll is in my App.Path folder
Public Declare Function thinBasic_Init Lib "thinCore.DLL" (ByVal hWnd As Long, _
ByVal cInstance As Long, _
ByVal sKey As String) As Long
Public Declare Function thinBasic_Release Lib "thinCore.DLL" (ByVal hScript As Long) As Long
Public Declare Function thinBasic_Run Lib "thinCore.DLL" (ByVal hScript As Long, _
ByVal sBuffer As String, _
ByVal BufferType As Long, _
Optional ByVal Options As Long, _
Optional ByVal DebugMode As Long, _
Optional ByVal LogMode As Long, _
Optional ByVal ObfuscateMode As Long, _
Optional ByVal CallingProgram As Long, _
Optional ByVal DependancyMode As Long) As Long
Public Const VarSubType_Byte = 1
Public Const VarSubType_Integer = 2
Public Const VarSubType_Word = 3
Public Const VarSubType_DWord = 4
Public Const VarSubType_Long = 5
Public Const VarSubType_Quad = 6
Public Const VarSubType_Single = 7
Public Const VarSubType_Double = 8
Public Const VarSubType_Currency = 9
Public Const VarSubType_Ext = 10
Public Const VarSubType_Variant = 50
Public Declare Function thinBasic_AddVariable_VB Lib "thinCore.DLL" ( _
ByVal vName As String, _
ByVal lValString As String, _
ByVal lValNumber As Double, _
ByVal ForceType As Long, _
Optional ByVal VarMemPtr As Long _
) As Long
Sample output after running;
Amount = 140.97
y = x + Amount
07:58:25 : y=141.22 : x=.25 : Amount=140.97
The thincore.dll which contains the new thinBasic_AddVariable_VB function can be download from here;
https://www.thinbasic.com/community/showthread.php?13270-Using-thincore-dll-with-Visual-Basic-6-0&p=96717&viewfull=1#post96717
Posting this mainly for my future reference,
but others might also be interested.
Joe
Joe Caverly
23-03-2024, 21:33
Hi Eros,
I've moved the thinCore.dll you created for me,
into my E:\thinBasic folder,
and have changed all the Declares in my VB6 code
to reflect the new location.
Public Declare Function thinBasic_Release Lib "E:\ThinBasic\thinCore.DLL" (ByVal hScript As Long) As Long
The reason I have done this,
is so I can use the thinBasic Modules.
I was hoping to just use the thinCore.dll by itself,
but it would seem it is how I have done it above,
or create a \LIB folder off of my VB6 Project Folder,
and copy only the required thinBasic Module to that folder.
I'm thinking that this might be the way to go,
as it eliminates having to install thinBasic on a system,
where I will deploy a VB6 app.
Mind you,
I can foresee maybe a DLLHell with possibly different copies of thincore.dll and,
for example, thinBasic_StringBuilder.dll,
available to individual VB6 projects.
Constructive suggestions appreciated.
Joe
ReneMiner
29-03-2024, 00:40
I don't think there is a WStringZ-version of it - these are to convert string containing numeric ASCII-notation to LongDouble (Ext)
Source may be Trim$(STR$(any_number)).
To be able to use CDECL in vb6 it requires a - by "TheTick" a talented programmer who made it to create the - fix for the on purpose by ms faulty developed and published with a comment as
"No absolutely impossible- that does not work. Its 100% incompatible"
export/import for cdecl (c-style-declarations)
that you can obtain from
https://www.vbforums.com/showthread.php?890388-VB6-VBCDeclFix-The-Add-in-allows-you-to-use-Cdecl-functions-in-VB6-IDE (https://www.vbforums.com/showthread.php?890388-VB6-VBCDeclFix-The-Add-in-allows-you-to-use-Cdecl-functions-in-VB6-IDE&highlight=)
DECLARE FUNCTION atoldbl CDECL Lib "msvcrt.dll" ALIAS "_atoldbl" (BYREF value AS EXT, BYREF str AS ASCIIZ) AS LONG
' for the below (from crtdefs.inc PB-Jose-Api)
TYPE threadlocinfo_inner_struct
locale AS ASCIIZ PTR ' char *
wlocale AS WSTRINGZ PTR ' wchar_t *
refcount AS LONG PTR ' int *
wrefcount AS LONG PTR ' int *
END TYPE
TYPE threadlocaleinfostruct
refcount AS LONG ' int
lc_codepage AS DWORD ' unsigned int
lc_collate_cp AS DWORD ' unsigned int
lc_handle(5) AS DWORD ' unsigned long lc_handle[6] ' LCID */
lc_id(5) AS LC_ID ' lc_id[6]; use 6! (thinbasic is 1-based)
lc_category(5) AS threadlocinfo_inner_struct ' lc_category[6]
lc_clike AS LONG ' int
mb_cur_max AS LONG ' int
lconv_intl_refcount AS LONG PTR ' int *
lconv_num_refcount AS LONG PTR ' int *
lconv_mon_refcount AS LONG PTR ' int *
lconv AS DWORD ' struct lconv * lconv;
ctype1_refcount AS LONG PTR ' int *
ctype1 AS WORD PTR ' unsigned short *
pctype AS WORD PTR ' unsigned short *
pclmap AS BYTE PTR ' const unsigned char *
pcumap AS BYTE PTR ' const unsigned char * pcumap
lc_time_curr AS DWORD ' struct __lc_time_data *
END TYPE
' // Size = 8 bytes
TYPE localeinfo_struct DWORD
locinfo AS DWORD ' pthreadlocaleinfostruct
mbcinfo AS DWORD ' pthreadmbcinfo
END TYPE
UNION locale_t DWORD
localeinfo_struct
quadinfo AS QUAD
END UNION
DECLARE FUNCTION atoldbl_l CDECL Lib "msvcrt.dll" ALIAS "_atoldbl_l" (BYREF value AS EXT, BYREF str AS ASCIIZ, OPTIONAL BYVAL locale AS locale_t) AS LONG
Instead of
"ByRef SomeVar as Whatever" you may use
"Byval pSomevar As Dword" and pass a pointer to the memory that contains even a fake/mimic-structure that is equal in size,
E.g.
when you exchange the declaration "Byref str as Asciiz" to "Byval pStr As Dword"
Dword pAsciiz=Heap_AllocByStr("987654321.23456789" & $NUL)
now you can simply pass pAsciiz for the pStr-Parameter
the locale seems confusing and i guess all the fuzz is about the kind of decimal delimiter, since the parameter is optional anyway -ommiting it will certainly default to dot (CHR$(0x2E))
Joe Caverly
29-03-2024, 01:53
It should not have to be this complicated to send a string from VB6 to thinBasic,
do something with it,
then send it back to VB6.
Now you are calling into the msvcrt.dll?
thinBasic is written in PowerBasic.
Take a look in your \PBWin10\samples\VB32\CapFirst folder.
If it can be done this easily with PowerBasic,
it should be easy to do with thinBasic.
BTW, it's "TheTrick",
not "TheTick"
Joe
ReneMiner
29-03-2024, 22:59
OK, other suggest
i just paste it from a powerbasic-source (part of a tb-module that i started to write)
memory-functions will be needed certainly more than once ,
for vb IMPORT replace by LIB
DECLARE SUB Memory_Zero IMPORT "KERNEL32.DLL" ALIAS "RtlZeroMemory" ( _
BYVAL Destination AS DWORD _ ' __in PVOID Destination
, BYVAL Length AS DWORD _ ' __in SIZE_T Length
) ' void
' for reset of some buffer
DECLARE FUNCTION Memory_Compare IMPORT "NTDLL.DLL" ALIAS "RtlCompareMemory" ( _
BYVAL Source1 AS DWORD _ ' __in const VOID *Source1
, BYVAL Source2 AS DWORD _ ' __in const VOID *Source2
, BYVAL Length AS DWORD _ ' __in SIZE_T Length
) AS DWORD
' = 0 if no difference over full length
' <> 0 position of the first different byte
DECLARE SUB Memory_Move IMPORT "KERNEL32.DLL" ALIAS "RtlMoveMemory" ( _
BYVAL Destination AS DWORD _ ' __in PVOID Destination
, BYVAL Source AS DWORD _ ' __in const VOID* Source
, BYVAL Length AS DWORD _ ' __in SIZE_T Length
) ' void
' allround for Memory-manipulation Copy/Poke,Memory_Get etc. , e.g. Poke Long/DWord for vb: simply "re-decorate" some of the above as
Declare Sub Poke_Long Lib "kernel32.dll" Alias "RtlMoveMemory" ( ByVal lpAddr As Long, ByRef Value As Long, Optional ByVal Bytes As Long = 4)
'
DECLARE SUB Memory_Fill IMPORT "KERNEL32.DLL" ALIAS "RtlFillMemory" ( _
BYVAL Destination AS DWORD _ ' __in PVOID Destination
, BYVAL Length AS DWORD _ ' __in SIZE_T Length
, BYVAL bFill AS BYTE _ ' __in BYTE Fill
) ' void
' for init/reset/redim etc.
'######################################################################################################################
' virtual memory
' --------------------------
DECLARE FUNCTION Virtual_Alloc LIB "Kernel32.dll" ALIAS "VirtualAlloc"( _
BYVAL lpAddress AS DWORD, BYVAL dwSize AS DWORD, _
BYVAL flAllocationType AS DWORD, BYVAL flProtect AS DWORD) AS DWORD
DECLARE FUNCTION Virtual_Free LIB "Kernel32.dll" ALIAS "VirtualFree"( _
BYVAL lpAddress AS DWORD, BYVAL dwSize AS DWORD, _
BYVAL dwFreeType AS DWORD) AS DWORD
MACRO MEM_COMMIT = &H00001000 'Replace Macro with Public/Private Const ... As Long =... for vb
MACRO MEM_RESERVE = &H00002000
MACRO MEM_RELEASE = &H00008000
MACRO PAGE_READWRITE = &H04 'allow read & write access
MACRO PAGE_EXECUTE_READWRITE = &H40 ' allow read, write and to execute directly from virtual memory
MACRO FUNCTION vAlloc(bcnt)=16+Virtual_Alloc(0,16+bcnt,MEM_COMMIT OR MEM_RESERVE,PAGE_READWRITE)
MACRO FUNCTION vFree(hmem)=Virtual_Free(hmem-16,0,MEM_RELEASE)
MACRO FUNCTION would be function for tb and Public Function for vb
bcnt (bytecount) as Long ' Do not allocate 1 GB or more at once, it might crash on some systems without pagefile and/or small storage
hMem As Long (VB) / As DWORD (tb)
the 16 bytes i added in front to store like the size and several flags & pointers for datatype-classification/dimensions counts + bounds/flags for encoding/relationships(parents, siblings) etc. to make it a class that carries all needed information about the stored data at the allocated memory
its similar to a strptr: the value in hMem is the pointer to the first byte of the string and the actually "correct pointer" is 16 bytes before
You may reduce or enlarge it to your specific needs - for strings you should probably store a length there, flags for encoding/zero-termination probably
Just be aware: calling declared functions from VB silently and without any further notice makes vb to convert STRINGS from UNICODE to ANSI and back. Avoid passing Variables that are defined as STRING in vb to any dll
some vb-helpers
convert a vb-string to a byte-array : THE RESULT IS UNCOMMON AS IT RETURNS AN ARRAY
Function StrToBlob(s as String) As Byte()
StrToBlob=StrConv(s, vbFromUnicode)
End Function
' and the reverse operation to it :
Function BlobToStr(b() As Byte) As String
BlobToStr = StrConv(b, vbUnicode)
End Function
Many parts, have fun with that puzzle :)
ReneMiner
31-03-2024, 06:40
to bring some light into the dark - and to avoid users wasting time on fruitless efforts concerning passing strings from vb1.0 to vb6.0 alias vb98 -
here is a link to some INFORMATION (https://classicvb.net/tips/varptr/)that to understand will make the difference and the minutes invested to read this will pay off through saving many hours and kilobytes of typing
If you want another way to bypass the hindrances THERE IS ONE (https://www.betaarchive.com/wiki/index.php/Microsoft_KB_Archive/176058) - and maybe another