Page 2 of 2 FirstFirst 12
Results 11 to 18 of 18

Thread: Using thincore.dll with Visual Basic 6.0

  1. #11
    thinBasic MVPs
    Join Date
    Oct 2012
    Location
    Germany
    Age
    54
    Posts
    1,533
    Rep Power
    171
    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")
    I think there are missing some Forum-sections as beta-testing and support

  2. #12
    thinBasic MVPs
    Join Date
    Oct 2012
    Location
    Germany
    Age
    54
    Posts
    1,533
    Rep Power
    171
    Ldbl only. Not that anyone could detect it
    I think there are missing some Forum-sections as beta-testing and support

  3. #13
    Member
    Join Date
    Feb 2023
    Location
    London, Ontario, Canada
    Posts
    34
    Rep Power
    5
    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/...ll=1#post96717

    Posting this mainly for my future reference,
    but others might also be interested.

    Joe

  4. #14
    Member
    Join Date
    Feb 2023
    Location
    London, Ontario, Canada
    Posts
    34
    Rep Power
    5
    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

  5. #15
    thinBasic MVPs
    Join Date
    Oct 2012
    Location
    Germany
    Age
    54
    Posts
    1,533
    Rep Power
    171

    because i just have it in front of me

    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
                      
    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))
    Last edited by ReneMiner; 29-03-2024 at 00:43.
    I think there are missing some Forum-sections as beta-testing and support

  6. #16
    Member
    Join Date
    Feb 2023
    Location
    London, Ontario, Canada
    Posts
    34
    Rep Power
    5
    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

  7. #17
    thinBasic MVPs
    Join Date
    Oct 2012
    Location
    Germany
    Age
    54
    Posts
    1,533
    Rep Power
    171
    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
    I think there are missing some Forum-sections as beta-testing and support

  8. #18
    thinBasic MVPs
    Join Date
    Oct 2012
    Location
    Germany
    Age
    54
    Posts
    1,533
    Rep Power
    171

    for some better understanding

    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 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 - and maybe another
    Last edited by ReneMiner; 31-03-2024 at 07:52.
    I think there are missing some Forum-sections as beta-testing and support

Page 2 of 2 FirstFirst 12

Similar Threads

  1. Where is latest thincore.inc file?
    By gddeluca in forum thinBasic General
    Replies: 4
    Last Post: 05-07-2021, 00:39
  2. Visual free basic
    By ReneMiner in forum Other languages
    Replies: 0
    Last Post: 25-05-2021, 04:49
  3. thinCore as embeddable 3rd party DLL
    By ErosOlmi in forum Suggestions/Ideas discussions
    Replies: 21
    Last Post: 04-09-2009, 01:11
  4. Replies: 12
    Last Post: 13-06-2009, 22:00
  5. Need confirmation on thinCore speed
    By ErosOlmi in forum thinBasic General
    Replies: 18
    Last Post: 12-10-2007, 10:36

Members who have read this thread: 15

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •