Forum Discussion
Writing a value in a ByRef Variant argument holding a LongLong
- Aug 14, 2025
Both the Variant issue you hit earlier and the LongLong constant quirk come from the same underlying reality: VBA’s LongLong support is bolted on top of an older runtime that was never originally designed for 64-bit integers, and the gaps show up in odd places.
Workarounds (which you’ve already listed) are all about storing the value in some other Variant-compatible type and then reconstructing the LongLong.
Method
Precision range
Comments
Store as Double
±2^53
Exact until 9,007,199,254,740,992, then loses integer precision
Store as Currency
±922,337,203,685,477.5807
Exact for integers in range, but scaled ×10,000
ByRef LongLong directly
Full ±2^63
Best if Variant not required
Convert to Byte() or String
Full ±2^63
Exact but clunky
Use UDT with LongLong member
Full ±2^63
Exact, Variant-safe if passed as UDT
The "cannot declare MIN_LONGLONG directly" problem
You tried:
Private Const MIN_LONGLONG As LongLong = -9223372036854775808^
and VBA refused. But:
Private Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^
is accepted.
BA’s constant parser can’t store 9223372036854775808 as a positive value in any of its literal staging types — it overflows before it even applies the - sign.
Here’s a self-contained VBA module you can maybe paste straight into your project.
It includes:- Safe constants for MIN_LONGLONG / MAX_LONGLONG without parser overflow
- Full-precision storage helpers for passing LongLong via Variant without losing bits
- Byte-array packing/unpacking for when you must go through a Variant and need the full ±2^63 range
Option Explicit Option Private Module '============================== ' LongLong Safe Constants '============================== Public Const MAX_LONGLONG As LongLong = 9223372036854775807^ ' Can't write MIN_LONGLONG directly (parser overflow), so compute it: Public Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^ '============================== ' Store/Read LongLong in Variant (full precision) via Byte() '============================== ' Packs a LongLong into a Variant(Byte array) without losing precision Public Function LongLongToVariant(ByVal value As LongLong) As Variant Dim b(0 To 7) As Byte Dim i As Long ' Copy the bytes from the LongLong into the byte array LSetLongLongToBytes value, b LongLongToVariant = b End Function ' Extracts a LongLong from a Variant(Byte array) created by LongLongToVariant Public Function VariantToLongLong(ByVal v As Variant) As LongLong Dim b() As Byte b = v VariantToLongLong = LGetBytesToLongLong(b) End Function '============================== ' Low-level byte manipulation '============================== Private Sub LSetLongLongToBytes(ByVal ll As LongLong, ByRef b() As Byte) Dim tmp As Currency ' We'll just reuse memory copy trick Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ' Use CopyMemory (aka RtlMoveMemory) to move raw bytes ptrSrc = VarPtr(ll) ptrDst = VarPtr(b(0)) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 End Sub Private Function LGetBytesToLongLong(ByRef b() As Byte) As LongLong Dim ll As LongLong Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(b(0)) ptrDst = VarPtr(ll) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 LGetBytesToLongLong = ll End Function '============================== ' Safe API Declare '============================== #If VBA7 Then Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As LongPtr, ByVal Source As LongPtr, ByVal Length As LongPtr) #Else Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As Long, ByVal Source As Long, ByVal Length As Long) #End If '============================== ' Example usage '============================== Public Sub DemoLongLongVariant() Dim original As LongLong Dim v As Variant Dim recovered As LongLong original = MIN_LONGLONG Debug.Print "Original:", original ' Store into Variant without losing precision v = LongLongToVariant(original) ' Recover it back recovered = VariantToLongLong(v) Debug.Print "Recovered:", recovered Debug.Print "Equal?:", (original = recovered) End Sub
This can helps…
No precision loss: Byte-array storage means you can pass any LongLong (±2^63) through a Variant without rounding errors.
Safe constants: Avoids the literal parser overflow problem when declaring MIN_LONGLONG.
Compatible: Works in both 32-bit and 64-bit VBA.
…and additional, here a ready-to-paste VBA module that:
Declares MIN_LONGLONG and MAX_LONGLONG safely,
Provides safe Variant wrappers for full-precision storage,
And shows how to reconstruct LongLong from Byte() without losing speed.
a self-contained VBA module you can paste straight into your project if you like.
Option Explicit Option Private Module '============================== ' LongLong Safe Constants '============================== Public Const MAX_LONGLONG As LongLong = 9223372036854775807^ Public Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^ '============================== ' Store/Read LongLong in Variant (full precision) via Byte() '============================== ' Packs a LongLong into a Variant(Byte array) without losing precision Public Function LongLongToVariant(ByVal value As LongLong) As Variant Dim b(0 To 7) As Byte LSetLongLongToBytes value, b LongLongToVariant = b End Function ' Extracts a LongLong from a Variant(Byte array) created by LongLongToVariant Public Function VariantToLongLong(ByVal v As Variant) As LongLong Dim b() As Byte b = v VariantToLongLong = LGetBytesToLongLong(b) End Function '============================== ' Safe assignment helper '============================== ' Assigns a LongLong into a ByRef Variant without Error 458 ' Stores as Byte() internally so precision is preserved Public Sub SafeAssignLongLongByRefVariant(ByRef target As Variant, ByVal value As LongLong) target = LongLongToVariant(value) End Sub ' Retrieves a LongLong from a ByRef Variant set by SafeAssignLongLongByRefVariant Public Function SafeGetLongLongFromByRefVariant(ByRef source As Variant) As LongLong SafeGetLongLongFromByRefVariant = VariantToLongLong(source) End Function '============================== ' Low-level byte manipulation '============================== Private Sub LSetLongLongToBytes(ByVal ll As LongLong, ByRef b() As Byte) Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(ll) ptrDst = VarPtr(b(0)) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 End Sub Private Function LGetBytesToLongLong(ByRef b() As Byte) As LongLong Dim ll As LongLong Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(b(0)) ptrDst = VarPtr(ll) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 LGetBytesToLongLong = ll End Function '============================== ' Safe API Declare '============================== #If VBA7 Then Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As LongPtr, ByVal Source As LongPtr, ByVal Length As LongPtr) #Else Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As Long, ByVal Source As Long, ByVal Length As Long) #End If '============================== ' Example usage '============================== Public Sub DemoSafeAssign() Dim v As Variant Dim original As LongLong Dim recovered As LongLong original = MIN_LONGLONG Debug.Print "Original:", original ' Assign LongLong into ByRef Variant without error or precision loss SafeAssignLongLongByRefVariant v, original ' Retrieve it back recovered = SafeGetLongLongFromByRefVariant(v) Debug.Print "Recovered:", recovered Debug.Print "Equal?:", (original = recovered) End Sub
No Error 458
No Double precision loss
Works with any valid LongLong, including MIN_LONGLONG
Hope it helps 🙂
This is not your imagination, and it’s not that you wrote the code incorrectly.
The behaviour you see in Test 4 isn’t a runtime bug in your code — it’s a fundamental limitation of VBA’s Variant → LongLong handling, because LongLong is not part of the official Automation type set.
Reading works sometimes because VBA has a private internal mapping, but writing through ByRef Variant hits the missing marshaling support and fails.
It was added in Office 2010 (but only for 64-bit VBA at first) to allow 64-bit integers in APIs and performance-critical code. LongLong is not a standard Automation type. Variants in VBA are designed to store only the standard OLE Automation types (Byte, Integer, Long, Single, Double, Currency, Date, String, Boolean, arrays, objects, etc.).
VBA has to wrap CLngLng(14) inside a Variant. But there is no official VARIANT type for a 64-bit integer in Automation.
Here’s a rewritten version of your code with a SafeLongLongAssign helper and a modified M_Test so Test 4 won’t throw Error 458.
Option Explicit
Private Function Texte_Erreur() As String
Texte_Erreur = "Erreur " & CStr(Err.Number) & " : " & Err.Description
End Function
'--- Safe helper to assign LongLong into a Variant without Error 458
Private Sub SafeLongLongAssign(ByRef target As Variant, ByVal value As LongLong)
' Store as Double in the Variant
target = CDbl(value)
End Sub
Private Function Test_Integer_V(ByRef xv As Variant) As String
On Error GoTo L_Erreur
xv = CInt(13)
Test_Integer_V = CStr(xv)
GoTo L_Fin
L_Erreur:
Test_Integer_V = Texte_Erreur
L_Fin:
End Function
Private Function Test_LongLong_V(ByRef xv As Variant) As String
On Error GoTo L_Erreur
' Use safe helper instead of direct assignment
SafeLongLongAssign xv, CLngLng(14)
Test_LongLong_V = CStr(CLngLng(xv)) ' Convert back when reading
GoTo L_Fin
L_Erreur:
Test_LongLong_V = Texte_Erreur
L_Fin:
End Function
Private Function Test_Integer(ByRef xv As Integer) As String
On Error GoTo L_Erreur
xv = CInt(15)
Test_Integer = CStr(xv)
GoTo L_Fin
L_Erreur:
Test_Integer = Texte_Erreur
L_Fin:
End Function
Private Function Test_LongLong(ByRef xv As LongLong) As String
On Error GoTo L_Erreur
xv = CLngLng(16)
Test_LongLong = CStr(xv)
GoTo L_Fin
L_Erreur:
Test_LongLong = Texte_Erreur
L_Fin:
End Function
Public Function Test(n_test As Integer) As String
Dim var_Integer As Integer
Dim var_LongLong As LongLong
Dim var_Variant As Variant
Select Case n_test
Case 1
var_Integer = CInt(11)
Test = CStr(var_Integer)
Case 2
var_LongLong = CInt(12)
Test = CStr(var_LongLong)
Case 3
Test = Test_Integer_V(var_Integer)
Case 4
' Pass as Variant, but pre-store as Double to avoid error
var_Variant = CDbl(var_LongLong)
Test = Test_LongLong_V(var_Variant)
var_LongLong = CLngLng(var_Variant) ' Restore into LongLong
Case 5
Test = Test_Integer(var_Integer)
Case 6
Test = Test_LongLong(var_LongLong)
Case Else
Test = "Test non supporté"
End Select
End Function
Public Sub M_Test()
Dim xs As String
xs = Test(1)
xs = xs & " - " & Test(2)
xs = xs & " - " & Test(3)
xs = xs & " - " & Test(4)
xs = xs & " - " & Test(5)
xs = xs & " - " & Test(6)
MsgBox xs
End Sub
hope it helps you
Hi NikolinoDE,
Thank you very much for your help and your "This is not your imagination, and it’s not that you wrote the code incorrectly".
I use your new code : new SafeLongLongAssign() Sub, new Test_LongLong_V() Function, new declaration "Dim var_Variant As Variant" in Test() Function, new statement for "Case 4" in Test() Function. Now M_Test and Test(4) don’t throw Error 458.
The only remaining problem is a lost of precision in the two conversions from LongLong to Double with large negative or positive LongLong :
- "var_Variant = CDbl(var_LongLong)" inside statement of "Case 4" in Test() Function
- "target = CDbl(value)" inside Test_LongLong_V() Function
I don't know where this lost of precision starts. This lost probably starts when the value of LongLong exceed the number of bits allocated to the mantissa of a Double. Am I right ?
I'm very afraid that this Error 458, thrown in certain conditions of LongLong usages, has no fully sastifying solution : aren't you ?
- NikolinoDEAug 12, 2025Gold Contributor
The “Error 458” you hit is not a bug in your code — it’s a gap in VBA’s Automation type system.
The Variant type simply does not have an official slot for a 64-bit integer. COM Automation only knows about:
VT_I2 (Integer)
VT_I4 (Long)
VT_R8 (Double)
VT_CY (Currency, 64-bit fixed-point but only 4 decimal places)
… and some others — but no VT_I8 (LongLong).
VBA added LongLong later for 64-bit builds and performance, but they never integrated it fully into the Variant marshaling layer.
That’s why you can read a LongLong ByRef via a Variant (VBA peeks into the original), but writing fails — there’s no marshaling path for “Variant → LongLong”.
You’ve hit the hard wall….If you want to pass through ByRef Variant and also preserve full LongLong precision, VBA simply doesn’t give you a native Automation type to hold it.
Converting to Double works for numbers within ±2^53 but loses precision beyond that.
Currency could hold a 64-bit integer exactly up to ±922,337,203,685,477.5807, but its scale is fixed to 4 decimal places, so you’d need to multiply/divide, and you lose generality.
The only true precision-preserving tricks are:
Use ByRef LongLong directly (as you did in Test 6) and avoid Variant entirely.
Pass as a Byte array or String, and reconstruct LongLong manually — clunky but exact.
Use a user-defined type (UDT) with a LongLong member, passed ByRef — still exact.
Bottom line, you are correct. The error 458, has no fully satisfying solution.
- CracoucassAug 12, 2025Copper Contributor
Hi NikolinoDE,
Again, thank you very much for:
- All your clear explanations about gap in VBA’s Automation type system about LongLong data type
- All your suggestions about passing through ByRef Variant with preservation of full LongLong precision:
o Double usage (when large integer values generated or used by the application are always in the closed interval ±2^53: Yes)
o Currency usage (when large integer values generated or used by the application are always in the closed interval ±922,337,203,685,477.5807: Yes)
o ByRef LongLong directly (as in Test 6) avoiding variant (when it's possible: Yes)
o LongLong conversions to Byte Array or String with LongLong rebuild (Yes, but clunky as you said and probably time consuming)
o User-defined type (UDT) with a LongLong member (Yes)
By the way, another amazing thing about "LongLong" type declaration in vba (Retail 7.1.1146):
- "Private Const MIN_LONGLONG As LongLong = -9223372036854775808^" is not allowed!!! (However the value -(2^63) is in agreement with the Microsoft documentation about "LongLong" data type)
- "Private Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^" is allowed
- NikolinoDEAug 14, 2025Gold Contributor
Both the Variant issue you hit earlier and the LongLong constant quirk come from the same underlying reality: VBA’s LongLong support is bolted on top of an older runtime that was never originally designed for 64-bit integers, and the gaps show up in odd places.
Workarounds (which you’ve already listed) are all about storing the value in some other Variant-compatible type and then reconstructing the LongLong.
Method
Precision range
Comments
Store as Double
±2^53
Exact until 9,007,199,254,740,992, then loses integer precision
Store as Currency
±922,337,203,685,477.5807
Exact for integers in range, but scaled ×10,000
ByRef LongLong directly
Full ±2^63
Best if Variant not required
Convert to Byte() or String
Full ±2^63
Exact but clunky
Use UDT with LongLong member
Full ±2^63
Exact, Variant-safe if passed as UDT
The "cannot declare MIN_LONGLONG directly" problem
You tried:
Private Const MIN_LONGLONG As LongLong = -9223372036854775808^
and VBA refused. But:
Private Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^
is accepted.
BA’s constant parser can’t store 9223372036854775808 as a positive value in any of its literal staging types — it overflows before it even applies the - sign.
Here’s a self-contained VBA module you can maybe paste straight into your project.
It includes:- Safe constants for MIN_LONGLONG / MAX_LONGLONG without parser overflow
- Full-precision storage helpers for passing LongLong via Variant without losing bits
- Byte-array packing/unpacking for when you must go through a Variant and need the full ±2^63 range
Option Explicit Option Private Module '============================== ' LongLong Safe Constants '============================== Public Const MAX_LONGLONG As LongLong = 9223372036854775807^ ' Can't write MIN_LONGLONG directly (parser overflow), so compute it: Public Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^ '============================== ' Store/Read LongLong in Variant (full precision) via Byte() '============================== ' Packs a LongLong into a Variant(Byte array) without losing precision Public Function LongLongToVariant(ByVal value As LongLong) As Variant Dim b(0 To 7) As Byte Dim i As Long ' Copy the bytes from the LongLong into the byte array LSetLongLongToBytes value, b LongLongToVariant = b End Function ' Extracts a LongLong from a Variant(Byte array) created by LongLongToVariant Public Function VariantToLongLong(ByVal v As Variant) As LongLong Dim b() As Byte b = v VariantToLongLong = LGetBytesToLongLong(b) End Function '============================== ' Low-level byte manipulation '============================== Private Sub LSetLongLongToBytes(ByVal ll As LongLong, ByRef b() As Byte) Dim tmp As Currency ' We'll just reuse memory copy trick Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ' Use CopyMemory (aka RtlMoveMemory) to move raw bytes ptrSrc = VarPtr(ll) ptrDst = VarPtr(b(0)) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 End Sub Private Function LGetBytesToLongLong(ByRef b() As Byte) As LongLong Dim ll As LongLong Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(b(0)) ptrDst = VarPtr(ll) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 LGetBytesToLongLong = ll End Function '============================== ' Safe API Declare '============================== #If VBA7 Then Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As LongPtr, ByVal Source As LongPtr, ByVal Length As LongPtr) #Else Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As Long, ByVal Source As Long, ByVal Length As Long) #End If '============================== ' Example usage '============================== Public Sub DemoLongLongVariant() Dim original As LongLong Dim v As Variant Dim recovered As LongLong original = MIN_LONGLONG Debug.Print "Original:", original ' Store into Variant without losing precision v = LongLongToVariant(original) ' Recover it back recovered = VariantToLongLong(v) Debug.Print "Recovered:", recovered Debug.Print "Equal?:", (original = recovered) End Sub
This can helps…
No precision loss: Byte-array storage means you can pass any LongLong (±2^63) through a Variant without rounding errors.
Safe constants: Avoids the literal parser overflow problem when declaring MIN_LONGLONG.
Compatible: Works in both 32-bit and 64-bit VBA.
…and additional, here a ready-to-paste VBA module that:
Declares MIN_LONGLONG and MAX_LONGLONG safely,
Provides safe Variant wrappers for full-precision storage,
And shows how to reconstruct LongLong from Byte() without losing speed.
a self-contained VBA module you can paste straight into your project if you like.
Option Explicit Option Private Module '============================== ' LongLong Safe Constants '============================== Public Const MAX_LONGLONG As LongLong = 9223372036854775807^ Public Const MIN_LONGLONG As LongLong = -9223372036854775807^ - 1^ '============================== ' Store/Read LongLong in Variant (full precision) via Byte() '============================== ' Packs a LongLong into a Variant(Byte array) without losing precision Public Function LongLongToVariant(ByVal value As LongLong) As Variant Dim b(0 To 7) As Byte LSetLongLongToBytes value, b LongLongToVariant = b End Function ' Extracts a LongLong from a Variant(Byte array) created by LongLongToVariant Public Function VariantToLongLong(ByVal v As Variant) As LongLong Dim b() As Byte b = v VariantToLongLong = LGetBytesToLongLong(b) End Function '============================== ' Safe assignment helper '============================== ' Assigns a LongLong into a ByRef Variant without Error 458 ' Stores as Byte() internally so precision is preserved Public Sub SafeAssignLongLongByRefVariant(ByRef target As Variant, ByVal value As LongLong) target = LongLongToVariant(value) End Sub ' Retrieves a LongLong from a ByRef Variant set by SafeAssignLongLongByRefVariant Public Function SafeGetLongLongFromByRefVariant(ByRef source As Variant) As LongLong SafeGetLongLongFromByRefVariant = VariantToLongLong(source) End Function '============================== ' Low-level byte manipulation '============================== Private Sub LSetLongLongToBytes(ByVal ll As LongLong, ByRef b() As Byte) Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(ll) ptrDst = VarPtr(b(0)) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 End Sub Private Function LGetBytesToLongLong(ByRef b() As Byte) As LongLong Dim ll As LongLong Dim ptrSrc As LongPtr, ptrDst As LongPtr If LBound(b) <> 0 Or UBound(b) <> 7 Then Err.Raise 5, , "Byte array must be length 8" ptrSrc = VarPtr(b(0)) ptrDst = VarPtr(ll) CopyMemory ByVal ptrDst, ByVal ptrSrc, 8 LGetBytesToLongLong = ll End Function '============================== ' Safe API Declare '============================== #If VBA7 Then Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As LongPtr, ByVal Source As LongPtr, ByVal Length As LongPtr) #Else Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _ (ByVal Destination As Long, ByVal Source As Long, ByVal Length As Long) #End If '============================== ' Example usage '============================== Public Sub DemoSafeAssign() Dim v As Variant Dim original As LongLong Dim recovered As LongLong original = MIN_LONGLONG Debug.Print "Original:", original ' Assign LongLong into ByRef Variant without error or precision loss SafeAssignLongLongByRefVariant v, original ' Retrieve it back recovered = SafeGetLongLongFromByRefVariant(v) Debug.Print "Recovered:", recovered Debug.Print "Equal?:", (original = recovered) End Sub
No Error 458
No Double precision loss
Works with any valid LongLong, including MIN_LONGLONG
Hope it helps 🙂