Page 19 of 19 FirstFirst ... 9171819
Results 181 to 190 of 190

Thread: Appendix Thread 2. ( Codes for other Threads, HTML Tables, etc.)

  1. #181
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Later

    kahhas
    Last edited by DocAElstein; Yesterday at 03:44 PM.

  2. #182
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    later

  3. #183
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    and later again

  4. #184
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Some notes in support of this forum post
    https://eileenslounge.com/viewtopic....313848#p313848


    Hello,

    If you have time to help me make some coding I am sharing to anyone work in more languages and operating system, then please follow the Instructions below.
    So far I have results for:
    Operating systems XP, Vista, Win 7, Win 8.1, Win 10, Win 11 German
    Operating systems Win 10, Win 11 English



    Instructions
    Download both files and put them anywhere, but both in the same place
    WSO_PropNames.xls https://app.box.com/s/ynlabyb11ekmj6m4we99wk9xd7gx0xn3
    sample.wmv https://app.box.com/s/leu06ql1fu9uzt59wnoizedg85qoo7k4

    Open just WSO_PropNames.xls, it should look something like this, with columns AA and AB empty
    https://i.postimg.cc/QN9RhZsF/Before...ll-Details.jpg

    Before Tabelle8 SchellGetNullDetails.JPG

    Now run the only macro in it, WSO_PropNames.xls and run Sub SchellGetNullDetails() ( Tabelle8.SchellGetNullDetails
    https://i.postimg.cc/wxCnB4T0/Tabell...ll-Details.jpg

    Tabelle8 SchellGetNullDetails.jpg


    After running that coding, you should see something approximately like this
    https://i.postimg.cc/ZRg2pVPY/After-...ll-Details.jpg

    After Tabelle8 SchellGetNullDetails.JPG



    Please now save the excel file and return it to me somehow: For example, post anywhere here at excelfox.com, or in that thread at https://eileenslounge.com , https://eileenslounge.com/viewtopic.php?f=30&t=40533

    Thanks,
    Alan
    Attached Files Attached Files
    Last edited by DocAElstein; 01-30-2024 at 09:39 PM.

  5. #185
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Some stuff to save for prosperity, related to this main forum post https://eileenslounge.com/viewtopic....315229#p315229
    https://eileenslounge.com/viewtopic....315235#p315235


    Some Microsoft documentation as of March 2024, here: https://learn.microsoft.com/en-us/of...rror-statement ( Just some of the first bits, relevant to the discussion at https://eileenslounge.com/viewtopic.php?f=30&t=40752 )


    On Error statement Article 03/30/2022

    Syntax
    On Error GoTo line
    On Error Resume Next
    On Error GoTo 0


    The On Error statement syntax can have any of the following forms:

    Statement Description
    On Error GoTo line Enables the error-handling routine that starts at line specified in the required line argument.
    The line argument is any line label or line number.
    If a run-time error occurs, control branches to line, making the error handler active.
    The specified line must be in the same procedure as the On Error statement; otherwise, a compile-time error occurs.
    On Error Resume Next Specifies that when a run-time error occurs, control goes to the statement immediately following the statement where the error occurred and execution continues. Use this form rather than On Error GoTo when accessing objects.
    On Error GoTo 0 Disables any enabled error handler in the current procedure.

    Remarks
    If you don't use an On Error statement, any run-time error that occurs is fatal; that is, an error message is displayed and execution stops.

    An "enabled" error handler is one that is turned on by an On Error statement; an "active" error handler is an enabled handler that is in the process of handling an error. If an error occurs while an error handler is active (between the occurrence of the error and a Resume, Exit Sub, Exit Function, or Exit Property statement), the current procedure's error handler can't handle the error. Control returns to the calling procedure.

    If the calling procedure has an enabled error handler, it is activated to handle the error. If the calling procedure's error handler is also active, control passes back through previous calling procedures until an enabled, but inactive, error handler is found. If no inactive, enabled error handler is found, the error is fatal at the point at which it actually occurred.

    Each time the error handler passes control back to a calling procedure, that procedure becomes the current procedure. After an error is handled by an error handler in any procedure, execution resumes in the current procedure at the point designated by the Resume statement. .........
    ........................
    Last edited by DocAElstein; 03-16-2024 at 02:04 PM.

  6. #186
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Some extra notes for these main forum posts
    https://www.excelfox.com/forum/showt...ll=1#post24163
    https://www.excelfox.com/forum/showt...age3#post24163
    https://eileenslounge.com/viewtopic....317547#p317547
    https://eileenslounge.com/viewtopic....317533#p317533


    This is the original coding from SamPi , which confused me a bit for a few reasons
    The choice of variable names;
    the use of a .xlam file; ( and
    the Class module is only part of the story
    )


    Class Module:
    Code:
    Option Explicit
     
    Public WithEvents App As Application
     
    Private Sub App_WorkbookOpen(ByVal Wb As Workbook)
    Dim s As String
    
    s = Wb.Name
    
    If s = "test.csv" Then MyMacro
    
    End Sub
    
    Sub MyMacro()
    MsgBox "Yes"
    End Sub
    
    ThisWorkbook:
    Code:
    Option Explicit
    
    Dim App             As New App
     
    Private Sub Workbook_Open()
         
       Set App.App = Application
    
    End Sub
    
    Attached Files Attached Files
    Last edited by DocAElstein; 05-22-2024 at 10:07 PM.

  7. #187
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Coding and possibly later extra notes for these main forum postings
    https://eileenslounge.com/viewtopic....323547#p323547
    https://www.excelfox.com/forum/showt...ll=1#post17882


    Code:
    Private Function DBugPrntArr(ByVal Arr As Variant) As Variant
    'ReDim DBugPrntArr(LBound(Arr) To UBound(Arr))
    Dim Var As Variant: ReDim Var(LBound(Arr) To UBound(Arr))
    Dim Eye As Long, strOut As String
        For Eye = LBound(Arr) To UBound(Arr)
         Let Var(Eye) = Arr(Eye)
         Let strOut = strOut & Arr(Eye) & ", "
        Next Eye
     Let strOut = "{" & Left(strOut, Len(strOut) - 2) & "}" '    Left(strOut, Len(strOut - 2))  is  Take off last  comma and space
    Debug.Print strOut
    Stop ' Check watch window on var    '  https://i.postimg.cc/fytpYm4V/Byte-Array.jpg
    End Function
    Private Sub StrConvBSTR()  '   https://www.excelfox.com/forum/showthread.php/2824/page2#post17882
    Rem 0
    Dim Bite As Byte: Let Bite = 0: Let Bite = 255 ' : Let Bite = 256     Let Bite = -1  ' Runtime error '6' Overflow
    Dim ByteArr() As Byte
    Dim BSTR As String, VBABString As String '   The Unicode character array that is pointed to by a BSTR must be preceded by a 4-byte length field and terminated by a single null 2-byte character (ANSI = 0)
     Let BSTR = "help": Debug.Print BSTR     ' help
     Let VBABString = BSTR         '   The variable  VBABString  is a pointer   to  the VB  pointer
     Let ByteArr() = BSTR    ' ### '   coerce string to array of bytes      ' 104 0 101 0 108 0 112 0
     ' 0b  https://eileenslounge.com/viewtopic.php?p=323085#p323085    https://eileenslounge.com/viewtopic.php?p=297500#p297500 (Second half)
    ' https://www.excelfox.com/forum/showthread.php/2824/page2#post17880
    Rem 1 … ... Unicode?
    Dim UnicChrArr As String, vTemp As Variant
     Let BSTR = "Alan"
     Let UnicChrArr = StrConv(BSTR, vbUnicode)
     ' Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(UnicChrArr) ' "h" & Chr(0) & "e" & Chr(0) & "l" & Chr(0) & "p" & Chr(0)
    
    
    ' 1b
      Let ByteArr() = StrConv(BSTR, vbUnicode)  ' ###                 ' 65 0 0 0 108 0 0 0 97 0 0 0 110 0 0 0
    Call DBugPrntArr(ByteArr()) '  {65, 0, 0, 0, 108, 0, 0, 0, 97, 0, 0, 0, 110, 0, 0, 0}    https://i.postimg.cc/qR2yq8xJ/Byte-Array-Unicode.jpg
    ' Let strArr() = StrConv(BSTR, vbUnicode) ' Type mismatch
      Let vTemp = StrConv(BSTR, vbUnicode)
     ' Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(vTemp)      ' "A" & Chr(0) & "l" & Chr(0) & "a" & Chr(0) & "n" & Chr(0)
    ' 1d
     Let ByteArr() = StrConv(StrConv(BSTR, vbFromUnicode), vbUnicode) ' 65 0 108 0 97 0 110 0
     Let vTemp = StrConv(StrConv(BSTR, vbFromUnicode), vbUnicode)     ' "Alan"
    Dim strArr() As String
     Let strArr() = Split(UnicChrArr, vbNullChar)                                        ' "A" "l" "a" "n" ""                                                               https://www.vbforums.com/showthread.php?526299-How-can-you-split-a-string-into-all-its-characters&p=3252316&viewfull=1#post3252316    http://gaffiprog.blogspot.com/2013/04/golfing-tip-vba-split-string-into.html
     Let strArr() = Split(Left(UnicChrArr, Len(UnicChrArr) - 1), vbNullChar) ' "A" "l" "a" "n"
    ' 1e
     Let strArr() = Split(Left(StrConv(BSTR, vbUnicode), Len(StrConv(BSTR, vbUnicode)) - 1), vbNullChar) ' "A" "l" "a" "n"   https://i.postimg.cc/7PQjwS7R/text-to-array.jpg
    
    Rem 2 "Unicode To ANSI"
    Debug.Print StrConv(BSTR, vbFromUnicode) ' ??  ' VB's "No idea how to display these characters as I don't even know what they are" (sometimes you might get a character, if the unicode byte pattern coincidentally matches a character in the current code page)
     Let vTemp = StrConv(BSTR, vbFromUnicode)
    Debug.Print vTemp ' ??                         ' VB's "No idea how ...
    ' Let strArr() = StrConv(s, vbFromUnicode) ' Type mismatch
    Dim varArr() As Variant
    ' Let varArr() = StrConv(s, vbFromUnicode) ' Type mismatch
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  '  65 108 97 110
    Debug.Print ByteArr()                          ' VB's "No idea how to ...
     Let ByteArr() = StrConv("Alan", vbFromUnicode) ' 65 108 97 110
    Call DBugPrntArr(ByteArr())      ' {65, 108, 97, 110}     '   https://i.postimg.cc/fytpYm4V/Byte-Array.jpg
    ' 2b Looking at a few characters of later interset
     Let BSTR = "help" & ChrW(8230)   '  "help" & "…"           8230      2026  …
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 133        ' https://i.postimg.cc/tTzWvZQN/Character-number-133-across-the-board.jpg
     Let BSTR = "help" & ChrW(133)  '    133 …               …        horizontal ellipsis        …       133      85 …   NEL   Next Line
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 65
     Let BSTR = "help" & Chr(133)  '    133 …               …        horizontal ellipsis        …       133      85 …   NEL   Next Line
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 133
     Let BSTR = "help" & "…"
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 133
     
     Debug.Print AscW(ChrW(8230)) ' 8330                  Wiki says
     Debug.Print Asc(ChrW(133))   '   63     ( 63 is ? )  Wiki says NEL   Next Line
     Debug.Print Asc(Chr(133))    '  133
     Debug.Print Asc("…")         '  133
     Debug.Print AscW("…")        ' 8230
      
     Let BSTR = "help" & ChrW(1000)  '            1000      3E8   ?   ?           Coptic Capital Letter Hori  Greek and Coptic
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 63    63 is ?
    ' 1c That Greek slanted AE which seems to have ChrW(482) and Chr(198)
     Let BSTR = "help" & ChrW(482)  '  (AE thing)   482      1E2    ?   ?        Latin Capital Letter ? with macron  for Sami   Phonetic & historic letters
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 63    63 is ?
    
     Let BSTR = "help" & ChrW(198)  '  (AE thing)  Latin Capital Letter ? with macron  for Sami    also    '    198 Æ               ?        Latin capital letter AE        Asc(left(range("A1").Value,1)) is 65    AscW(left(range("A1").Value,1)) is 198      198 Æ               ?        Latin capital letter AE        ?       198      C6 ?   ?      Latin Capital letter ?   "Letters: Uppercase ""
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 198
    Debug.Print "Æ" & " " & Asc("Æ") & " " & AscW("Æ") '  Æ 198 198
     Let BSTR = "help" & ChrW(65535)  '              65535      FFFF ?
     Let ByteArr() = StrConv(BSTR, vbFromUnicode)  ' 104 101 108 112 63
    
    ' 1d Showing perhaps the ignorance
     Let UnicChrArr = "A" & vbNullChar & "E" & vbNullChar
    Debug.Print UnicChrArr '   A E
    Debug.Print StrConv(UnicChrArr, vbFromUnicode) ' AE
     Let ByteArr() = StrConv(UnicChrArr, vbFromUnicode)
    
    End Sub
    

    Ref
    https://www.eileenslounge.com/viewto...297326#p297326 https://www.eileenslounge.com/viewto...297329#p297329
    https://eileenslounge.com/viewtopic....323085#p323085
    https://www.excelfox.com/forum/showt...age2#post17880
    Last edited by DocAElstein; 12-30-2024 at 04:12 PM.

  8. #188
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Coding for these main forum posts
    https://eileenslounge.com/viewtopic....324039#p324039
    https://www.excelfox.com/forum/showt...age2#post11883
    https://eileenslounge.com/viewtopic....324064#p324064

    From Mike(SpeakEasy), here https://eileenslounge.com/viewtopic....324039#p324039
    Code:
     Option Explicit
    
    Private Declare Function StrTrim Lib "shlwapi.dll" Alias "StrTrimA" (ByVal psz As String, ByVal pszTrimChars As String) As Long ' we'll be passing vb string to api
    Private Declare Function StrTrimTrick Lib "shlwapi.dll" Alias "StrTrimA" (ByVal psz As Long, ByVal pszTrimChars As Long) As Long ' we'll be passing the StrPtr to API
    
    Public Sub trimmy()
        Dim a As String
        Dim b As String
        
        a = "Hello" & ChrW(257) ' add a non-extended ASCII (i.e non 'ANSI') unicode character
        b = a
        
        Debug.Print a
        Debug.Print a = b
        Debug.Print AscW(Right(a, 1))
    
        StrTrim a, "" ' call an 'ANSI' API function that does nothing to a string, so we'd expect the same string we passed in ...
        Debug.Print a
        Debug.Print a = b ' Oh
        Debug.Print AscW(Right(a, 1)) ' Oh dear
        
    End Sub
    
    Public Sub trimmy2()
        Dim a As String
        Dim b As String
        
        a = "Hello" & ChrW(257) ' add a non-extended ASCII (i.e non 'ANSI') unicode character
        b = a
        
        Debug.Print a
        Debug.Print a = b
        Debug.Print AscW(Right(a, 1))
    
        StrTrimTrick StrPtr(a), StrPtr("") ' call 'trick' version of 'ANSI' API function that does nothing to a string, so we'd expect the same string we passed in ...
        Debug.Print a
        Debug.Print a = b ' hurrah
        Debug.Print AscW(Right(a, 1)) ' as we'd expect
        
    End Sub
    My versions of those, and a third coding that is almost identical to the second of mine
    Code:
    Option Explicit
    Private Declare Function StrTrim Lib "shlwapi.dll" Alias "StrTrimA" (ByVal psz As String, ByVal pszTrimChars As String) As Long ' we'll be passing vb string to api
    Private Declare Function StrTrimTrick Lib "shlwapi.dll" Alias "StrTrimA" (ByVal psz As Long, ByVal pszTrimChars As Long) As Long ' we'll be passing the StrPtr to API
    Private Declare Function StrTrimTrickW Lib "shlwapi.dll" Alias "StrTrimW" (ByVal psz As Long, ByVal pszTrimChars As Long) As Long ' we'll be passing the StrPtr to API
    '  https://eileenslounge.com/viewtopic.php?p=324039#p324039
    Public Sub JimmyJimmyRiddleA() '  https://www.youtube.com/watch?v=66CCLS0do7c
    Rem 0
    Dim a As String, b As String, Boo As Boolean
     Let a = "Hello" & ChrW(257)   ' add a non-extended ASCII (i.e non 'ANSI') unicode character (a with a small thing on top)
     Let b = a
    Rem 1
    Debug.Print ChrW(257), a: Let Range("A1") = a ' Immediate Window don't do Unicorn , Excel Spreadsheet does
    Debug.Print a = b
    Debug.Print AscW(Right(a, 1)), AscW(Right(Range("A1").Value, 1)), Len(a) '   257     257     6
    Rem 2 ' call an 'ANSI' API function that does nothing to a string, so we'd expect the same string we passed in ...
    Let Boo = StrTrim(a, "") ' Boo is False
    Debug.Print a: Let Range("A1") = a
    Debug.Print a = b ' Oh, it's False
    Debug.Print AscW(Right(a, 1)), Len(a) ' 97     6   Oh dear
        
    End Sub
    Public Sub JimmyJimmyRiddleAW() '  https://www.youtube.com/watch?v=Pgqa3cVOxUc
    Rem 0
    Dim a As String, b As String, Boo As Boolean
     Let a = "Hello" & ChrW(257)    ' add a non-extended ASCII (i.e non 'ANSI') unicode character (a with a small thing on top)
     Let b = a
    Rem 1
    Debug.Print ChrW(257), a: Let Range("A1") = a
    Debug.Print a = b
    Debug.Print AscW(Right(a, 1)) ' True
    Rem 2 '  call ( Implicit W ) 'trick' version of 'ANSI' API function that does nothing to a string, so we'd expect the same string we passed in ...
     Let Boo = StrTrimTrick(StrPtr(a), StrPtr(""))
    Debug.Print a
    Debug.Print a = b ' True,   hurrah
    Debug.Print AscW(Right(a, 1)) ' as we'd expect
    End Sub
    Public Sub JimmyJimmyRiddleW() '  https://www.youtube.com/watch?v=RMEOy-SkX0k
    Rem 0
    Dim a As String, b As String, Boo As Boolean
     Let a = "Hello" & ChrW(257)    ' add a non-extended ASCII (i.e non 'ANSI') unicode character (a with a small thing on top)
     Let b = a
    Rem 1
    Debug.Print ChrW(257), a: Let Range("A1") = a
    Debug.Print a = b
    Debug.Print AscW(Right(a, 1)) ' True
    Rem 2 '  call  Emplicit W  'trick' version of Wide API function that does nothing to a string, so we'd expect the same string we passed in ...
     Let Boo = StrTrimTrickW(StrPtr(a), StrPtr(""))
    Debug.Print a
    Debug.Print a = b ' True,   hurrah
    Debug.Print AscW(Right(a, 1)) ' as we'd expect
    End Sub
    Last edited by DocAElstein; 01-11-2025 at 02:28 PM.

  9. #189
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Coding for this Post
    https://www.excelfox.com/forum/showt...ll=1#post24943
    Code:
    Private Declare Function StrTrim Lib "shlwapi.dll" Alias "StrTrimA" (ByVal psz As String, ByVal pszTrimChars As String) As Boolean '  '  Straight AASI          -   we'll be passing vb string to api         ' https://learn.microsoft.com/en-us/windows/win32/api/shlwapi/nf-shlwapi-strtrima
    Private Declare Function StrTrimWU Lib "shlwapi.dll" Alias "StrTrimW" (ByVal psz As Long, ByVal pszTrimChars As Long) As Boolean '  '  Straight AASI          -   we'll be passing vb string to api         ' https://learn.microsoft.com/en-us/windows/win32/api/shlwapi/nf-shlwapi-strtrima
    Sub BSTR_LPWSTR() ' https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-Pasting-API-Cliipboard-issues-and-Rough-notes-on-Advanced-API-stuff?p=24943&viewfull=1#post24943
    Rem 1
    Dim strBSTR As String, strNew As String, Boo As Boolean, pz1PWSTR As Long, pz2PWSTR As Long
    '  "vbNullString  state"
    Debug.Print VarPtr(strBSTR) '        1831480     This could be regarded as getting me the variable, strBSTR. It is the symbol for the pointer stored on the COFF symbol table
    Debug.Print VarPtr(ByVal strBSTR) '      0       Our Pointer is empty at this point
     
    '  "Zero length string state"
     Let strBSTR = ""
    Debug.Print VarPtr(strBSTR)      '   1831480     There is no reason for this to change
    Debug.Print VarPtr(ByVal strBSTR) '  195893860   We now have something significant that we can definitely relate to a string character storage
    '  "A" state
     Let strBSTR = "A"
    Debug.Print VarPtr(strBSTR)      '   1831480     There is no reason for this to change
    Debug.Print VarPtr(ByVal strBSTR) '  195894740   We now have something significant that we can definitely relate to a string character storage
    
    Rem 2  LPWSTR v BSTR
    ' 2a) VBA
     Let strBSTR = "Pog" & Chr(0) & " ": Debug.Print strBSTR & "Z"  '  Pog  Z
    'Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(strBSTR)             '  "Pog" & Chr(0) & " "
    ' 2b) api  Trim
     Let strNew = strBSTR ' A pointer to the null-terminated string to be trimmed. When this function returns successfully, it receives the trimmed string.
     Let Boo = StrTrim(strNew, " ")                     '    Boo is  False  - nothing was trimmed
    'Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(strNew)              '   "Pog" & Chr(0) & " "
     Let Boo = StrTrimWU(StrPtr(strNew), StrPtr(" "))   '    Boo is  False  - nothing was trimmed
    'Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(strNew)             '  "Pog" & Chr(0) & " "
    ' 2c) VBA  Trim
     Let strNew = Trim(strBSTR): Debug.Print strNew & "Z"           '  Pog Z
    'Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(strNew)              '  "Pog" & Chr(0)
    
    End Sub

  10. #190
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Coding for this main forum question
    https://eileenslounge.com/viewtopic....324964#p324964
    https://eileenslounge.com/viewtopic....324975#p324975



    Code:
    Option Explicit  ' Destination Points to the starting address of the copied block’s destination.            Source Points to the starting address of the block of memory to copy               Length Specifies the size, in bytes, of the block of memory to copy.
     #If VBA7 Then
      Private Declare PtrSafe Sub VBGetTarget Lib "kernel32" Alias "RtlMoveMemory" (Target As Any, ByVal lPointer As LongPtr, ByVal cbCopy As LongPtr)
     #Else
      Private Declare Sub VBGetTarget Lib "kernel32" Alias "RtlMoveMemory" (Target As Any, ByVal lPointer As Long, ByVal cbCopy As Long)
     #End If
    Sub LongType() '        https://www.excelfox.com/forum/showthread.php/2404-Notes-tests-ByVal-ByRef-Application-Run-OnTime-Multiple-Variable-Arguments-ByRef-ByVal?p=11888&viewfull=1#post11888     https://www.excelfox.com/forum/showthread.php/2404-Notes-tests-ByVal-ByRef-Application-Run-OnTime-Multiple-Variable-Arguments-ByRef-ByVal/page4    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-Pasting-API-Cliipboard-issues-and-Rough-notes-on-Advanced-API-stuff?p=17881&viewfull=1#post17881
    Dim LngDest As Long, LngSource As Long
    Rem 1  Biggest long number
    ' 1a)
     Let LngSource = 1073741824 + 1073741823 ' =2147483647      1073741824 is 2^30 which is the last but 1 (31th counting from the right), of 32 bits in the 32 Bit binary representation of a number       1073741823 is the resulting decimal you get if you have a 1 in the first 30, counting from the right, of a binary number         decimal 2147483647 is in binary 31 digits  1111111111111111111111111111111
    VBGetTarget LngDest, VarPtr(LngSource), 4 ' Anything less than 4 will give the wrong number
    Debug.Print LngDest '   2147483647     (31 digits 1111111111111111111111111111111)
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 3
    Debug.Print LngDest '    16777215      (24 digits 111111111111111111111111)
    
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 2
    Debug.Print LngDest '    65535         (16 digits 1111111111111111)
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 1
    Debug.Print LngDest '     255          (8 digits 11111111)
    
    
    Rem 2  Small long number
     Let LngSource = 2
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 4
    Debug.Print LngDest '      2
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 3
    Debug.Print LngDest '      2
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 2
    Debug.Print LngDest '      2
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 1
    Debug.Print LngDest '      2
    
    
    Rem 3  Number decimal  511    (9 digits 111111111)
     Let LngSource = 511
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 2
    Debug.Print LngDest '      511          (9 digits 111111111)
     
     Let LngDest = 0
    VBGetTarget LngDest, VarPtr(LngSource), 1
    Debug.Print LngDest '      255          (8 digits 11111111)
     
     
     Let LngDest = 0 '          LngSource = 511   ->  (9 digits 111111111)
    VBGetTarget LngDest, VarPtr(LngSource) + 1, 1
    Debug.Print LngDest '      1             ( 00000001  )
    End Sub



    Share ‘kernel32.dll’ https://app.box.com/s/124tsibbnl7pk1xz7assmzivuyyfplo3
    Share ‘rpiAPI.dll’ https://app.box.com/s/xfng1rft9mawgcpxlu5z64pps2sg7grv
    Attached Files Attached Files
    Last edited by DocAElstein; 02-07-2025 at 03:44 PM.

Similar Threads

  1. VBA to Reply All To Latest Email Thread
    By pkearney10 in forum Outlook Help
    Replies: 11
    Last Post: 12-22-2020, 11:15 PM
  2. Appendix Thread. Diet Protokol Coding Adaptions
    By DocAElstein in forum Test Area
    Replies: 6
    Last Post: 09-05-2019, 10:45 AM
  3. Replies: 19
    Last Post: 04-20-2019, 02:38 PM
  4. Search List of my codes
    By PcMax in forum Excel Help
    Replies: 6
    Last Post: 08-03-2014, 08:38 AM

Posting Permissions

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