Results 1 to 22 of 22

Thread: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

  1. #1

    Thread Starter
    Hyperactive Member
    Join Date
    Feb 2015
    Location
    Colorado USA
    Posts
    269

    Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    I would like to make sure my programs are LARGEADDRESSAWARE so that they can run in a 3-4 GB process space. The obvious problem seems to be that if pointers are treated internally as signed Longs and the sign bit is set (as it will be for anything between 2 and 4 GB) then when we add offsets to pointers that we can run into obvious problems.

    It seems that either VB6/VBA is capable of doing this or not and if not then there isn't much we can do about it other than make sure we don't run in memory spaces above 2 GB.

    But assuming that our native code is capable of this then we have to check our code. At first I thought we would have to jump through XOR hoops to deal with offsets but upon further reflection I don't think we have to. To some extent it hinges on how our hidden pointer functions (StrPtr, VarPtr and ObjPtr) deal with these. I don't know how they deal with addresses with the sign bit set. I am hopeful that they treat the values not as signed Longs (and choke on them) but actually return the values with the sign bit set. If they don't then we are likely hosed.

    If they do return unsigned values into our signed Long variables then I think we have already solved the problem. A great example is dealing with the 64-bit file size returned by FindFirstFile and FindNextFile. We have to flip the two Long values into one Currency variable to get the correct file size (i.e., the API calls return the DWords in the wrong order for us). Up to now I do something like the following:

    Code:
    PutMem4 VarPtr(.Size), rawData.lngFileSizeLow
    PutMem4 VarPtr(.Size) + 4&, rawData.lngFileSizeHigh
    I thought I was going to have to do this:

    Code:
    PutMem4 VarPtr(.Size), rawData.lngFileSizeLow
    #If Win32 then
    PutMem4 ((VarPtr(.Size) Xor &H80000000) Xor 4&) Xor &H80000000, lngFileSizeHigh
    #Else
    PutMem4 VarPtr(.Size) + 4&, rawData.lngFileSizeHigh
    #End If
    Wow! What a mess each time I have an offset to a pointer.

    But I got to thinking about this and I have convinced myself I don't need to do that. The problem I am trying to avoid is a bad pointer addition when the base value is a negative from being a signed Long) and we add to it. I believe it all works itself out.

    Suppose I have a pointer that is -268435456 (&HF000000) and I want to add 4 to it. So the answer in hex should be &HF0000004 if it is truly added to it (ignoring the sign bit). Well, if you take -268435456 and add 4 to it you get -268435452 which is &HF0000004, exactly what we need.

    So I don't think I need to go back and adjust all of my pointer arithmetic for offsets to pointer values from StrPtr, VarPtr and ObjPtr, at least if they return unsigned values in the first place.

    Do you agree? If so, can you see any other changes we would need to make to our code to make it LARGEADDRESSAWARE?

  2. #2
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    If you are going to add/subtract to/from a pointer, then caution should be applied if there is any chance of crossing over the sign bit. There are threads on "pointer math". No need to reinvent the wheel.

    VB6 is always in a 32 bit process. VBA (64 bit) has the PtrSafe keyword

    Edited: A workaround to access a range of bytes at any memory address, to avoid pointer math, is to use a SafeArray (byte array) overlayed on the target memory address. Then you can access the individual bytes by referencing the array elements, i.e., myData(0-n).
    Last edited by LaVolpe; May 23rd, 2018 at 07:54 PM.
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  3. #3
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    With pointers often you only need forward offsetting by small offsets with no zero-crossing, so a simple expression will work:

    Code:
    Option Explicit
    
    Private Function FHex(ByVal Value As Long) As String
        FHex = Right$("0000000" & Hex$(Value), 8)
    End Function
    
    Private Sub Test(ByVal Ptr As Long, ByVal Offset As Long)
        Debug.Print FHex(Ptr), FHex(Offset),
        On Error Resume Next
        Debug.Print FHex(Ptr + Offset),
        If Err Then Debug.Print Err.Description,
        Err.Clear
        Debug.Print FHex(&H80000000 Xor ((&H80000000 Xor Ptr) + Offset))
        If Err Then Debug.Print Err.Description
    End Sub
    
    Private Sub Main()
        Debug.Print "Ptr", "Offset", "Add", "Forward offset"
        Test 0, 1
        Test &H7FFFFFFF, 1
        Test &H80000000, 1
        Test &HFFFFFFFF, 1
    End Sub
    Code:
    Ptr           Offset        Add           Forward offset
    00000000      00000001      00000001      00000001
    7FFFFFFF      00000001      Overflow      80000000
    80000000      00000001      80000001      80000001
    FFFFFFFF      00000001      00000000      Overflow
    Last edited by dilettante; May 23rd, 2018 at 09:27 PM.

  4. #4
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,156

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Quote Originally Posted by MountainMan View Post
    But I got to thinking about this and I have convinced myself I don't need to do that. The problem I am trying to avoid is a bad pointer addition when the base value is a negative from being a signed Long) and we add to it. I believe it all works itself out.

    Suppose I have a pointer that is -268435456 (&HF000000) and I want to add 4 to it. So the answer in hex should be &HF0000004 if it is truly added to it (ignoring the sign bit). Well, if you take -268435456 and add 4 to it you get -268435452 which is &HF0000004, exactly what we need.

    So I don't think I need to go back and adjust all of my pointer arithmetic for offsets to pointer values from StrPtr, VarPtr and ObjPtr, at least if they return unsigned values in the first place.

    Do you agree?
    No and here is why. Let me give you a counter-example:

    1. Take address &H7FFFFFF0 (2147483632)
    2. Add &H20 (32)
    3. Should come as &H80000010 (2147483664)

    But when using signed Longs in VB6 you get overflow error on the second step above.

    So what is the point of XOR trick?

    Notice that signed Longs have no trouble adding &HFFFFFFF0 + &H20 = &H00000010 i.e. clearing the signed bit does not raise overflow error. The idea of the XOR trick is to temporary shift addition's first operand, so that values around &H80000000 (the 2GB boundary) come towards 0 where boundary crossing *is* supported by signed Longs. After the addition is performed the second XOR returns the result back towards 2GB boundary.

    The XOR trick is designed to implement "unsigned + signed" addition i.e. the second operand is still *signed* so that you can substract offsets from some (unsigned) base pointer.

    The XOR trick cannot add unsigned offsets (as it would still overflow 2GB boundary) but if you think about it this use-case is actually never applicable in 32-bit apps (Ptr1 + Ptr2? Why would you add pointers?).

    There is equivalent XOR trick for subtraction (Ptr1 - Ptr2) go get offset b/n two unsigned pointers. Here is an UnsignedDiff implemented with even more XORs.

    cheers,
    </wqw>

  5. #5

  6. #6
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Hmmm, Trick, your reply sort of begs a question. How would we run the IDE in a Large Address Aware mode? If I were going to use this LARGEADDRESSAWARE option with the linker during compilation, I'd love to test it in the IDE.

    However, here are all the command line options I see:

    Name:  cide.jpg
Views: 1639
Size:  55.6 KB

    To my eyes, it looks like it's going to take some very deep VB6.EXE hack to make this work. Maybe I'm missing something.

    Best Regards,
    Elroy
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  7. #7

  8. #8
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Wow, I'm impressed. Now you've got me wanting to spelunk into my VB6.EXE and change this setting. *chuckles* I actually doubt I will though. Even though my primary project is large, I don't think I'm anywhere close to the 2Gig limit.

    Good info though.

    Take Care,
    Elroy
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  9. #9
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Just to be clear, we're talking about changing this bit, correct?

    Code:
    
    Option Explicit
    '
    Private Type IMAGE_DOS_HEADER
        e_magic                     As Integer
        e_cblp                      As Integer
        e_cp                        As Integer
        e_crlc                      As Integer
        e_cparhdr                   As Integer
        e_minalloc                  As Integer
        e_maxalloc                  As Integer
        e_ss                        As Integer
        e_sp                        As Integer
        e_csum                      As Integer
        e_ip                        As Integer
        e_cs                        As Integer
        e_lfarlc                    As Integer
        e_ovno                      As Integer
        e_res(0 To 3)               As Integer
        e_oemid                     As Integer
        e_oeminfo                   As Integer
        e_res2(0 To 9)              As Integer
        e_lfanew                    As Long
    End Type
    '
    Private Type IMAGE_FILE_HEADER
        Machine                         As Integer
        NumberOfSections                As Integer
        TimeDateStamp                   As Long
        PointerToSymbolTable            As Long
        NumberOfSymbols                 As Long
        SizeOfOptionalHeader            As Integer
        Characteristics                 As Integer
    End Type
    '
    Private Type IMAGE_DATA_DIRECTORY
        VirtualAddress                  As Long
        Size                            As Long
    End Type
    '
    Private Type IMAGE_OPTIONAL_HEADER
        Magic                           As Integer
        MajorLinkerVersion              As Byte
        MinorLinkerVersion              As Byte
        SizeOfCode                      As Long
        SizeOfInitializedData           As Long
        SizeOfUnitializedData           As Long
        AddressOfEntryPoint             As Long
        BaseOfCode                      As Long
        BaseOfData                      As Long
        ImageBase                       As Long
        SectionAlignment                As Long
        FileAlignment                   As Long
        MajorOperatingSystemVersion     As Integer
        MinorOperatingSystemVersion     As Integer
        MajorImageVersion               As Integer
        MinorImageVersion               As Integer
        MajorSubsystemVersion           As Integer
        MinorSubsystemVersion           As Integer
        W32VersionValue                 As Long
        SizeOfImage                     As Long
        SizeOfHeaders                   As Long
        CheckSum                        As Long
        Subsystem                       As Integer
        DllCharacteristics              As Integer
        SizeOfStackReserve              As Long
        SizeOfStackCommit               As Long
        SizeOfHeapReserve               As Long
        SizeOfHeapCommit                As Long
        LoaderFlags                     As Long
        NumberOfRvaAndSizes             As Long
        DataDirectory(0 To 15)          As IMAGE_DATA_DIRECTORY
    End Type
    '
    Private Type IMAGE_NT_HEADERS
        Signature                       As Long
        FileHeader                      As IMAGE_FILE_HEADER
        OptionalHeader                  As IMAGE_OPTIONAL_HEADER
    End Type
    '
    Private Enum NtFileHeaderCharacteristicsEnum
        IMAGE_FILE_RELOCS_STRIPPED = &H1&           ' Relocation information is stripped from the file.
        IMAGE_FILE_EXECUTABLE_IMAGE = &H2&          ' The file is executable (there are no unresolved external references).
        IMAGE_FILE_LINE_NUMS_STRIPPED = &H4&        ' Line numbers are stripped from the file.
        IMAGE_FILE_LOCAL_SYMS_STRIPPED = &H8&       ' Local symbols are stripped from file.
        IMAGE_FILE_AGGRESIVE_WS_TRIM = &H10&        ' Aggressively trim the working set.
        IMAGE_FILE_LARGE_ADDRESS_AWARE = &H20&      ' The application can handle addresses larger than 2 GB.
        IMAGE_FILE_BYTES_REVERSED_LO = &H80&        ' Bytes of word are reversed.
        IMAGE_FILE_32BIT_MACHINE = &H100&           ' Computer supports 32-bit words.
        IMAGE_FILE_DEBUG_STRIPPED = &H200&          ' Debugging information is stored separately in a .dbg file.
        IMAGE_FILE_REMOVABLE_RUN_FROM_SWAP = &H400& ' If the image is on removable media, copy and run from the swap file.
        IMAGE_FILE_NET_RUN_FROM_SWAP = &H800&       ' If the image is on the network, copy and run from the swap file.
        IMAGE_FILE_SYSTEM = &H1000&                 ' System file.
        IMAGE_FILE_DLL = &H2000&                    ' DLL file.
        IMAGE_FILE_UP_SYSTEM_ONLY = &H4000&         ' File should be run only on a uniprocessor computer.
        IMAGE_FILE_BYTES_REVERSED_HI = &H8000&
    End Enum
    '
    
    Private Sub Form_Click()
        Dim hFile               As Long
        Dim DosHeader           As IMAGE_DOS_HEADER
        Dim NtHeaders           As IMAGE_NT_HEADERS
        Dim Characteristics     As Long
        '
    
        hFile = FreeFile
        Open "C:\Program Files (x86)\Microsoft Visual Studio\VB98\VB6.exe" For Binary As hFile
        '
        Get hFile, 1, DosHeader
        Get hFile, DosHeader.e_lfanew + 1, NtHeaders
        '
        Close hFile
    
        '
        ' Let's just report the value for now.
        Characteristics = NtHeaders.FileHeader.Characteristics
    
        MsgBox "All characteristics (shouldn't be zero): " & Hex$(Characteristics)
        MsgBox "IMAGE_FILE_LARGE_ADDRESS_AWARE value in VB6.EXE:" & vbCrLf & vbCrLf & CBool(Characteristics And IMAGE_FILE_LARGE_ADDRESS_AWARE)
    
    
    End Sub
    
    
    EDIT1: Also, for those running Windows 32-bit, notice I've hard-coded the VB6.EXE path. You'll have to patch that up for Win32 systems.
    Last edited by Elroy; May 24th, 2018 at 10:59 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  10. #10

  11. #11
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    And yet another question comes to mind. Who's to say that Microsoft, when writing the IDE, did all of their pointer arithmetic with unsigned longs? However, I suppose the IDE will be running down in the low memory of whatever memory page it's running in. So it'd just be the p-code that we wrote that we'd need to be careful about.

    EDIT1: I suppose this also answers the VBA portion of this question too. I just checked EXCEL.EXE for Office 14, and the bit was OFF. It'd sure make me a bit nervous to turn it on for Office executables, but it'd be an interesting test. Trick's code in post #7 would certainly be a good test.
    Last edited by Elroy; May 24th, 2018 at 10:57 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  12. #12

  13. #13

    Thread Starter
    Hyperactive Member
    Join Date
    Feb 2015
    Location
    Colorado USA
    Posts
    269

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Excel 2013 and Excel 2016 recently got the capability to run with LARGEADDRESSAWARE in their 32-bit versions. Since it was announced as a big thing and since it isn't available for earlier versions of Excel I am guessing that it likely requires something more than just setting that bit in the header.

  14. #14

    Thread Starter
    Hyperactive Member
    Join Date
    Feb 2015
    Location
    Colorado USA
    Posts
    269

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    I agree that crossing the boundary of max signed Long is the issue with pointer arithmetic. I have done some timing to see which approach is best and I compared the results to just adding the base and offset for pointer arithmetic.

    #1 - Unsigned addition routine from wqweto
    #2 - pvSafePointerAdd from LaVolpe
    #3 - Inline : NewPtr = ((Pntr Xor &H80000000) + Adder) Xor &H80000000
    #4 - Inline : NwPntr = &H80000000 Xor ((&H80000000 Xor Pntr) + Adder)
    #5 - Inline Ignoring sign bit (what we do now) : NewPntr = Pntr + Adder

    Looping Times to do 10,000,000 loops (average of twice each)

    #1 690
    #2 797
    #3 130
    #4 130
    #5 94

    Not worrying about the sign bit is obviously the fastest but isn't going to work for LARGEADDRESSAWARE. Inline solutions #3 and #4 are the best alternate options I have found and I am using #3 in my code now. Note also that a typical RtlMoveMemory, GetMemx or PutMemx doesn't need this unless there is addition or subtraction from a pointer found with StrPtr, VarPtr or ObjPtr.

    BTW, the PtrSafe item we use in API calls in later versions of Excel does absolutely nothing other than make us feel good. You can easily take any declaration and include PtrSafe in it and Excel will run it (or crash). I don't believe the declaration does anything at all so the purpose is to force us coders to look at the declaration and see which Longs are really pointers and change them to LongPtr. The code doesn't do this for us; we have to do it ourselves. So the PtrSafe doesn't really do anything for VBA programmers that we have to do in VB.

  15. #15
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE


  16. #16

    Thread Starter
    Hyperactive Member
    Join Date
    Feb 2015
    Location
    Colorado USA
    Posts
    269

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Large Address Aware capability for Excel just covers the internal Excel code and enables access to up to 3 GB on 32-bit systems and 4 GB on 64-bit systems. So it looks like the MSoft Office crew has gone through their code and ensured no busts at the signed Long boundary. The capability of Windows to make the 3 or 4 GB available to 32-bit processes is nothing special to Excel; it is enabled automatically on all newer versions of 64-bit Windows and with a switch in autoexec.bat it is available in 32-bit Windows. Whether an individual program can take advantage of this capability is totally up to the program.

    But the questions I have are related to VBA code we may write in Excel &/or VB6 code we may write as standalone programs. Nothing the Excel programmers have done make our code able to access this extra memory without crashing if we don't do our pointer arithmetic correctly. Also, we do have access to the extra RAM and can use it if we simplify our coding to not use any pointer arithmetic... Obviously that shouldn't be a problem because as we all know VB and VBA don't even use pointers because us VB/VBA programmers wouldn't understand those more difficult concepts...

  17. #17
    Frenzied Member
    Join Date
    Jan 2010
    Posts
    1,103

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Code:
    Private Function PtrAdd1(thePointer As Long, AmountToAdjust As Long) As Long
    '    'Lavolpe
    '    'http://www.vbforums.com/showthread.php?795693-RESOLVED-Pointer-Arithmetic&p=4931477#post4931477
         Dim xAdj As Long
         Const SIGN_BIT = &H80000000
         If AmountToAdjust < 0& Then xAdj = SIGN_BIT
         PtrAdd1 = ((thePointer Xor SIGN_BIT) + (AmountToAdjust Xor xAdj)) Xor (SIGN_BIT Xor xAdj)
    'End Function
    
    
    Private Function PtrAdd2(ByVal ptr As Long, ByVal Offset As Long) As Long
    ' Unsigned Pointer addition
    ' avoids integer overflow when incrementing past 2GB Boundary
    ' needed for /LARGEADDRESSAWARE processes on 64bit Windows
        'http://www.vbforums.com/showthread.php?795693-RESOLVED-Pointer-Arithmetic&p=4931477#post4931477
        'http://www.vbforums.com/showthread.php?862179-ReplaceAny-and-TrimAny-Function&p=5285601&viewfull=1#post5285601
        'http://www.vbforums.com/showthread.php?816793-VB6-DLL-for-Unsigned-Long-amp-Integer-Arithmetic
        'http://www.vbforums.com/showthread.php?828867-VB6-Code-Snippet-Load-Language-Specific-resource-String-FindResourceEx
        Const SIGN_BIT As Long = &H80000000
        PtrAdd2 = SIGN_BIT Xor (SIGN_BIT Xor ptr) + Offset
    End Function
    
    
    Private Function UnsignedAdd(ByVal lUnsignedPtr As Long, ByVal lSignedOffset As Long) As Long
        'https://github.com/wqweto/VbRtcc/blob/master/src/mdRtcc.bas#L176-L183
        'wqweto
        '--- note: safely add *signed* offset to *unsigned* ptr for *unsigned* retval w/o overflow in LARGEADDRESSAWARE processes
        UnsignedAdd = ((lUnsignedPtr Xor &H80000000) + lSignedOffset) Xor &H80000000
    End Function
    Are above functions the same?

  18. #18
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    @Jonney, in the thread you referenced in my "function" above, you'll notice it was designed to overcome a problem when adding very large offsets (post #5 in that thread). Otherwise, it's a modification to the one that you credited to wqweto

    Note: Though this thread talks specifically about pointers, this "math" issue can also relate to incrementing/decrementing Longs for use as Record IDs
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  19. #19
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,156

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    @LaVolpe: As far as I understand in PtrAdd1 param AmountToAdjust is signed.

    Can you give an example where PtrAdd1 succeeds but PtrAdd2 fails to justify the extra lines in there?

    cheers,
    </wqw>

  20. #20
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Quote Originally Posted by wqweto View Post
    @LaVolpe: As far as I understand in PtrAdd1 param AmountToAdjust is signed.
    Yes

    Quote Originally Posted by wqweto View Post
    Can you give an example where PtrAdd1 succeeds but PtrAdd2 fails to justify the extra lines in there?
    The thread I linked to in my previous reply, post #5 on that thread
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  21. #21
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Quote Originally Posted by LaVolpe View Post
    Yes

    The thread I linked to in my previous reply, post #5 on that thread
    Those posts by bonnie don't make sense if the offset is signed...
    Code:
    ? "&H"; Hex$((&H1 Xor SIGN_BIT) + &HFFFFFFFE Xor SIGN_BIT)          '<-- Throws RTE 6: Overflow
    'Result should've been &HFFFFFFFF
    
    1 + -2 = into unsigned should overflow...
    
    ? "&H"; Hex$((&HFFFFFFFF Xor SIGN_BIT) - &HFFFFFFFE Xor SIGN_BIT)   '<-- Throws RTE 6: Overflow
    'Result should've been &H1&
    
    similarly UINT_MAX - (-2) is the same as UINT_MAX + 2, should also overflow.
    if you are using offsets that are unsigned though - that makes more sense. The signed offset works only with values less than 2G.

    if you are adding or subtracting an unsigned offset bigger than 2G, then yeah you have to use LaVolpes (PtrAdd1). This scenario is totally feasible with a large binary disk images or bitmaps.

    PtrAdd2 is limited to adding and subtracting 32bit signed offsets. (smaller than 2G)
    Last edited by DEXWERX; May 25th, 2018 at 08:04 AM.

  22. #22
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,156

    Re: Making 32-bit VB6/VBA Code LARGEADDRESSAWARE

    Some edge cases still overflow (which is expected and mostly harmless)
    thinBasic Code:
    1. '
    2.     Dim ptr As Long
    3.    
    4.     ptr = &H7FFFFFF0
    5.     Debug.Print Hex(PtrAdd1(ptr, &H20))
    6.     Debug.Print Hex(PtrAdd2(ptr, &H20))
    7.    
    8.     ptr = &H80000010
    9.     Debug.Print Hex(PtrAdd1(ptr, -&H20))
    10.     Debug.Print Hex(PtrAdd2(ptr, -&H20))
    11.    
    12.     ptr = &H10
    13.     Debug.Print Hex(PtrAdd1(ptr, -(ptr + &H20)))
    14.     Debug.Print Hex(PtrAdd2(ptr, -(ptr + &H20)))    '<--- overflow
    15.    
    16.     ptr = -&H10
    17.     Debug.Print Hex(PtrAdd1(ptr, &H20))             '<--- overflow
    18.     Debug.Print Hex(PtrAdd2(ptr, &H20))             '<--- overflow
    cheers,
    </wqw>

Posting Permissions

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



Click Here to Expand Forum to Full Width