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

Thread: Rough Notes, and posts to be referenced from elsewhere, on VBA Windows API

  1. #11
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,455
    Rep Power
    10
    This is page 2
    https://www.excelfox.com/forum/showt...dows-API/page2
    https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API/page2
    This is post #11 forum post24916
    https://www.excelfox.com/forum/showt...dows-API/page2
    https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API/page2
    This is post #11 forum post24916
    https://www.excelfox.com/forum/showt...ll=1#post24916
    https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API/page2
    https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API?p=24916&viewfull=1#post24916





    Some notes, codings etc. in support of some other posts
    https://eileenslounge.com/viewtopic....321979#p321979
    https://www.excelfox.com/forum/showt...ll=1#post24904


    Getting some windows identification info
    .

    Main coding courtesy of Dev Ashish, http://access.mvps.org/access/api/api0013.htm
    ( and https://eileenslounge.com/viewtopic....321978#p321978 )
    I did some minor adjustments, mostly in output to suit my own experiments

    Code:
    ' Original main Code Courtesy of Dev Ashish  http://access.mvps.org/access/api/api0013.htm  and  https://eileenslounge.com/viewtopic.php?p=321978#p321978
    '
    Private Declare Function apiGetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
    Private Declare Function apiGetDesktopWindow Lib "user32" Alias "GetDesktopWindow" () As Long
    Private Declare Function apiGetWindow Lib "user32" Alias "GetWindow" (ByVal Hwnd As Long, ByVal wCmd As Long) As Long
    Private Declare Function apiGetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal Hwnd As Long, ByVal nIndex As Long) As Long
    Private Declare Function apiGetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal Hwnd As Long, ByVal lpString As String, ByVal aint As Long) As Long
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Const mcGWCHILD = 5
    Private Const mcGWHWNDNEXT = 2
    Private Const mcGWLSTYLE = (-16)
    Private Const mcWSVISIBLE = &H10000000 '  Watch window gives  268435456 (even when no code is running)
    Private Const mconMAXLEN = 255
    
    Public Sub fEnumWindows()
    ' For worksheet output, not important for understanding the main coding
    Dim Ws As Worksheet: Set Ws = ThisWorkbook.Worksheets.Item(1)
    Dim Lc As Long, Lr As Long: Let Lc = Ws.Cells.Item(2, Ws.Columns.Count).End(xlToLeft).Column
     Let Ws.Cells.Item(1, Lc + 1) = CreateObject("WScript.Network").ComputerName & "      " & Format(Now(), "ddd,dd,mmm,yyyy")                  '  Environ$("computername")      Nigel Heffernan  https://stackoverflow.com/questions/3551055/how-to-get-name-of-the-computer-in-vba/10108951#10108951
     Let Ws.Cells.Item(2, Lc + 1) = "Hwnd": Let Ws.Cells.Item(2, Lc + 2) = "Class Name": Let Ws.Cells.Item(2, Lc + 3) = "Caption": Let Ws.Cells.Item(2, Lc + 4) = "Hwnd( Caption)": Let Ws.Cells.Item(2, Lc + 5) = "enum visible?"
    
    
    Dim lngx As Long, lngLen As Long, lngStyle As Long, strCaption As String
     Let lngx = apiGetDesktopWindow(): Debug.Print "Geted Desktop Window  " & lngx & " " & " CLass name " & fGetClassName(lngx)
     Let lngx = apiGetWindow(lngx, mcGWCHILD): Debug.Print "   First child to Desktop " & lngx & " CLass name " & fGetClassName(lngx) '   GW_CHILD = 5    The topmost of the given window's child windows. This has the same effect as using the GetTopWindow function, ... usually at the top of all the other children in the Z-order
        Do While Not lngx = 0 ' We are looping "equal level children", seperated not realy, just look seperate to us because of the seen to us z order
         Let strCaption = fGetCaption(lngx)
    '        If Len(strCaption) > 0 Then ' Those without a caption seem not important
             Let lngStyle = apiGetWindowLong(lngx, mcGWLSTYLE) '  apiGetWindowLong gets info,   GWL_STYLE  -16  retrieves the window styles
                ' For   enum visible windows only
    '            If lngStyle And mcWSVISIBLE Then   '
                 Let Lr = Ws.Cells.Item(Ws.Rows.Count, Lc + 1).End(xlUp).Row                                                    '  Handle             Class name          Caption
                    If lngStyle And mcWSVISIBLE Then
                     Let Ws.Cells.Item(Lr + 1, Lc + 5) = "enum visible " & lngStyle & " And " & mcWSVISIBLE
                    Else
                     'Let Ws.Cells.Item(Lr + 1, Lc + 5) = lngStyle & " And " & mcWSVISIBLE
                    End If
                 Let Ws.Cells.Item(Lr + 1, Lc + 6) = lngStyle: Ws.Cells.Item(Lr + 1, Lc + 7) = mcWSVISIBLE
                 Debug.Print FindWndNumber(lpClassName:=fGetClassName(lngx), lpWindowName:=vbNullString), fGetClassName(lngx); Tab(50); fGetCaption(lngx); Tab(100); FindWndNumber(lpClassName:=vbNullString, lpWindowName:=fGetCaption(lngx))
                 Let Ws.Cells.Item(Lr + 1, Lc + 1) = lngStyle & " " & FindWndNumber(lpClassName:=fGetClassName(lngx)): Let Ws.Cells.Item(Lr + 1, Lc + 2) = fGetClassName(lngx): Let Ws.Cells.Item(Lr + 1, Lc + 3) = fGetCaption(lngx): Let Ws.Cells.Item(Lr + 1, Lc + 4) = FindWndNumber(lpClassName:=vbNullString, lpWindowName:=fGetCaption(lngx))
    '            End If
    '        End If
         Let lngx = apiGetWindow(lngx, mcGWHWNDNEXT) '  GW_HWNDNEXT = 2   The window below the given window in the Z-order.
        Loop ' While Not lngx = 0  ' I am going through all the child windows of the desktop windows
    End Sub
    Private Function fGetCaption(Hwnd As Long) As String
    Dim strBuffer As String, intCount As Integer
     Let strBuffer = String$(Number:=255 - 1, Character:="0") ' "00000000000000000000000000000000..........000"
     Let intCount = apiGetWindowText(Hwnd:=Hwnd, lpString:=strBuffer, aint:=255) ' This makes  strBuffer  something like    *MSCTFIME UI 0000000000000000............000"
        If intCount > 0 Then Let fGetCaption = Left$(strBuffer, intCount)
    End Function
    Private Function fGetClassName(Hwnd As Long) As String
    Dim strBuffer As String, intCount As Integer
     Let strBuffer = String$(255 - 1, 0)
     Let intCount = apiGetClassName(Hwnd, strBuffer, mconMAXLEN)
        If intCount > 0 Then
         Let fGetClassName = Left$(strBuffer, intCount)
        End If
    End Function
    
    

    I got up to date more recently on my API references, https://eileenslounge.com/viewtopic....322050#p322050 , so I was able to understand a lot of that coding above.
    But the logic of If lngStyle And mcWSVISIBLE Then confused me a bit, even though I understand what it is doing.
    Investigating what typically finds its way into the coding at that line revealed that it is fed some big numbers on either side of the And , ( a fixed number on the right, varied numbers on the left).
    I could not see how it becomes True in some numbers and not on others. It is obviously not a simple thing since at first glance there is no obvious pattern to what numbers give true: We typically seem to have some spread of big numbers, positive and negative. Example numbers in the next screen shot in column B and C. The results in column D are typical of what I got in a few ways with VBA codings, and they seem to be doing something similar to that code line with the same numbers as the code line typically gets, and they get the same results.
    So its something to do with how in VBA , this sort of thing works

    If ___ And ___ Then
    Code:
    Sub TestStrangeIfAndLogic()
    Range("D2:D20").ClearContents
    Dim Rw As Long
        For Rw = 2 To 20
            If Range("B" & Rw).Value And Range("C" & Rw).Value Then Let Range("D" & Rw) = "True?"
        Next Rw
    End Sub
    Sub TestStrangeIfAndLogicArr()
    Range("D2:D20").ClearContents
    Dim Rw As Long, arrRws() As Variant: Let arrRws() = Range("A1:C20").Value
        For Rw = 2 To 20
            If arrRws(Rw, 2) And arrRws(Rw, 3) Then Let Range("D" & Rw) = "True?"
        Next Rw
    End Sub
    
    https://i.postimg.cc/NMg25kxm/Strang...wo-numbers.jpg Strange If __ And __ Then logic with two numbers.JPG



    I went off to get some help, https://eileenslounge.com/viewtopic.php?f=30&t=41610

    I got some good help, and the next few posts discus the issues, and get the final solutions and final understanding, which in initially looked like it would be fairly simple, after the help I got, but turned out to be a bit more complicated, mainly as I had never heard of …." 2’s Compliment Computer Codswollop" ( https://www.aimathcoach.com/en/mathg...olution_guide/
    https://www.excelfox.com/forum/showt...ll=1#post24921
    )

    I start looking at this issue in more detail in the next few post
    Last edited by DocAElstein; Yesterday at 07:55 PM.

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

    If lngStyle And mcWSVISIBLE Then

    If lngStyle And mcWSVISIBLE Then


    If lngStyle And mcWSVISIBLE Then
    Some notes, codings etc. in support of some other posts
    https://eileenslounge.com/viewtopic....321979#p321979 https://eileenslounge.com/viewtopic.php?f=30&t=41610
    https://www.excelfox.com/forum/showt...l=1#post249016


    Introduction
    A code line from the last post
    , If lngStyle And mcWSVISIBLE Then

    What’s going on? – Hans told me …. The number is looked at by VBA in its binary representation form, and each corresponding Bit at the same horizontal position for the two numbers is compared. This is referred to as bitwise AND of the binary representation of the numbers.
    In simple terms, If at any position both are 1 , then the result will be true…..


    It all started here:
    I had some strange results that I did not understand. It boiled down to some code lines such as this returning True
    If -1811939328 And 268435456 Then
    , whilst similar such as this returning False
    If -2046820352 And 268435456 Then
    At first glance there is no thing obvious to see to explain the difference in behaviour in the two examples

    So, because ExcelFox is the adult thinking man’s forum, we are going to have a good look at it.




    Knowing the answer, or appearing to be close to knowing it, suggests we want initially to get those two decimals into some String like " 0 1 " representation of a number( Binary computer stuff " 0 0 0 1 0 1 1 0 1 " )
    A couple of points to consider
    _(i) A string type representation of a lot of 0s and 1s is a good idea so that we don’t have problems with things like leading 0s vanishing when Excel or VBA messes with the format of a number we may write: In binary computer things the number will have typically some fixed character length, so we should not mess with that, or let Excel or VBA mess with it
    _(ii) The first Bit/first position is always reserved for the sign character, (which is 1 for a negative number, and that sort of leads to the phenomena that Anding two negative numbers always results in a True. But it is not quite so straight forward always.
    It's an artefact, perhaps, of both how computers store negative numbers and the bit wise way that the VBA And works.

    The following function to convert a decimal to binary is useful to know about and understand, but bare in mind that solving the main issue ended up being a bit more involved.

    A simple function to get the string like binary 0s and 1s representation of a number.
    The basic idea:
    (To keep it simple initially in this first summary, we will not concern ourselves directly with the actual unbar of digits in the binary string of 1s and 0s )
    It’s basically all based on the school maths way of converting a decimal to binary…. Take the decimal number and divide it by a number got from a high power of 2;
    __ If that division comes out >= 1 , then you have your first binary digit, starting from the left of 1; then you subtract that number which was the high power of 2 from the decimal number , so the decimal number under consideration is now smaller
    __ Else when that division comes out < 1 , then you have your first binary digit of 0 starting from the left. You leave the decimal number at the size it is.
    Now you do the same again using the next power of 2 down as the denominator to get the next binary digit to the right. Eventually you are down to (2 ^0) to get the last binary digit at the right

    The actual implementation in the coding.
    We decide on some length limit for the string. For now, based on an initial quick empirical look and guess, I will go for up to 30 powers of 2, ( (2 ^ N) = (2 ^ 30) ). I might change that later based on experience. A big one initially will hopefully catch numbers as big as we have. This means the string length will be 32 characters, as in the string like binary 0s and 1s representation we have (2 ^ 0) at the right, (2 ^ 30) at the left, and also an extra sign bit included to be the **first left character. ( ** As it turns out it is not quite as simple as that )

    A simple function can be one that builds the string….
    , first with a 0 or 1 is added to the string depending on if the decimal number being converted is negative or positive
    , then we successively divide the number by (2 ^ N) where N goes from 30 to 0.
    __ If the result of the division results in 1 or 1 and a fraction more, we add** ( ** add as in including another character, via a & "1" not maths add + ) a "1" to the string, and reduce the decimal number by that used (2 ^ N) , before moving to the next N.
    __ Else the division results in less than 1, then we add a 0, (and do not reduce the decimal value)
    , then move on to the next N
    Code:
    Sub TestNumberInBinary()
    Debug.Print NumberInBinary(9)         ' 00000000000000000000000000001001
    Debug.Print NumberInBinary(268435456) ' 00010000000000000000000000000000
    End Sub
    Public Function NumberInBinary(ByVal DecNumber As Long) As String
    Rem 1 A negative number in a computer binary representation has a  1  at the first character position
     Let NumberInBinary = IIf(DecNumber < 0, "1", "0")
    Rem 2  we successively divide the number by (2 ^ N) where N goes from 30 to 0. If the result of the division results in 1 or 1 and a fraction more, we add** ( ** add as in including another character, not maths add ) a 1 to the string, and reduce the decimal number by that (2 ^ N) before moving to the next N. If the division resilts in less than 1, we add a 0, then move on to the next N Divide the decimal number by 2 to the power of N, with N geting smaller. Every tine the resulting number is equal or bigger than 1  the binary bit would be 1 and the decimal number we reduce by that 2 to the N, and keep going
    Dim N As Long
        For N = 30 To 0 Step -1  '  30 seems to be the limit before something is too big
            If DecNumber / (2 ^ N) >= 1 Then
             Let NumberInBinary = NumberInBinary & "1"
             Let DecNumber = DecNumber - (2 ^ N)
            Else
             Let NumberInBinary = NumberInBinary & "0"
            End If
        Next N
    End Function

    A function to mimic the behaviour of the VBA And with numbers is very easy.
    Simply
    _ convert the two decimal numbers to a string in the form of the computer binary 0s and 1s representation, (using for example the function I did above)
    _ then starting from the left compare the characters in the corresponding position in the two strings. As soon as you get a 1 in both , you make the functions returned output as True and exit the function, otherwise the function returns false if you never get a pair of 1s at the same horizontal position

    Code:
    Public Function NumbersInVBAIf_And_Then(ByVal Dec1 As Long, Dec2 As Long) As Boolean
    Rem 1 the two decimal numbers to a string in the form of the computer binary 0s and 1s representation
    Dim Bin1 As String, Bin2 As String ' String representation helps prevent loosing leading 0's
     Let Bin1 = NumberInBinary(Dec1): Bin2 = NumberInBinary(Dec2)
    Rem 2 starting from the left compare the characters in the corresponding position in the two strings. As soon as you get a 1 in both , you make the functions returned output as True and exit the function, otherwise the function returns false if you never get a pair of 1s
    Dim TPwr As Long
        For TPwr = 1 To 32 Step 1
         If Mid(Bin1, TPwr, 1) = 1 And Mid(Bin2, TPwr, 1) = 1 Then Let NumbersInVBAIf_And_Then = True: Exit Function
        Next TPwr
    End Function
    Conclusions, … Oh dear
    I thought it was too good to be true. It did tons of tests, my coding is sound, and definitely does what I think it should with all data extremes
    It doesn’t’ get the right bloody results though: ….Compare… as before, column D ( which effectively does what the main full codng does ) which gets the correct results.
    Based on everything so far, this is the test coding to get results in column E
    Code:
    Sub TryMyFuncsNumberInBinaryNumbersInVBAIf_And_Then()
    Range("E2:E20").Clear
    Dim Rw As Long, arrRws() As Variant: Let arrRws() = Range("A1:C20").Value
        For Rw = 2 To 20
         Let Range("E" & Rw) = NumbersInVBAIf_And_Then(arrRws(Rw, 2), arrRws(Rw, 3))
        Next Rw
    
    End Sub
    The results, however, speak for themselves..
    https://i.postimg.cc/2jxYmcbH/Bollox.jpg
    Bollox.JPG




    Bollox


    .... continued in next post
    Last edited by DocAElstein; Yesterday at 08:58 PM.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,455
    Rep Power
    10

    Two's complement

    …. Continued from last post….
    ( …. as the saying goes, Two's complement, (three’s probably some other crazy idiotic computer mathematicians abortion) )

    Bollox, what went wrong
    It did not take long to find the problem. .. VBA ( and most computer stuff) apparently does not always use the simple binary logic

    Just to review what I was dong, the simple binary logic: So I was following the simple logic like..
    A number 7 is somehow in computer binary a variation of
    Code:
                8 4 2 1
    0 0 0 0 0 0 0 1 1 1
    , and correspondingly -7 I was thinking , (and in a few places I was even seeing stated….)
    Code:
                8 4 2 1
    1 0 0 0 0 0 0 1 1 1
    It aint quite like that, , ( at last in most modern day computer things)
    It seems mostly we have something called Two's complement
    Crazy, but some computer dick thought it up:. This is the basic jist of it; ….. For the negative number, you do a few weird things…..
    _ you first turn the positive number upside down / flip / invert or call it what you want to get this ( 0s become 1’s and visa versa )
    Code:
                8 4 2 1
    1 1 1 1 1 1 1 0 0 0
    _ Now you do a math add of 1,
    ( but important is that you do it in base 2 -
    1+0 = 1
    1+1 =0 and carry over a 1 to add to the next to the left
    etc.
    )
    Code:
                8 4 2 1
    1 1 1 1 1 1 1 0 0 1
    That’s it, Crazy, but that's how it goes: in most computer systems, -7 would have the form something of the form
    1 1 1 1 1 1 1 0 0 1
    Just to get that clear, especially the add in base 2 bit, the same again for binary 6, and binary (2’s compliment) -6.
    First the positive number, 6
    Code:
                8 4 2 1
    0 0 0 0 0 0 0 1 1 0
    Now, for -6 …..
    First a flip of the "normal" binary for 6
    Code:
                8 4 2 1
    1 1 1 1 1 1 1 0 0 1
    , next, the final step, is to add the 1, in binary maths, which is base 2. So as it is base 2, you wont get a 2 furthest right. You get a 0 and then have to carry the 1 over to the next left****, so you get finally for -6
    Code:
                8 4 2 1
    1 1 1 1 1 1 1 0 1 0
    ( **** A nice Laymen way of thinking about adding a 1 in binary, is to start from the right and try to find an " empty" place ( i.e., a 0 ), to dump the 1 in . )


    If the positive number was 4, then to get -4, after the flip, you would have had to carry over the added 1 twice and so finally for -4 you would have
    Code:
                8 4 2 1
    1 1 1 1 1 1 1 1 0 0
    Compare that with positive 4 and you can see its easy to get confused
    Code:
                8 4 2 1
    0 0 0 0 0 0 0 1 0 0



    So, what went wrong?
    So we know now what the 2’s codswallop is all about, … how does that explain the failings of the last post

    The second function is sound. – Just to review that: The basic idea, as Hans said , is that in a VBA If … And … Then with two numbers either side of the And , the first thing to do is convert the two numbers to binary, and then, do a bitwise And
    , - just for convenience show them in the same vertical plane…..
    Example:
    6 And 5
    Code:
                8 4 2 1
    0 0 0 0 0 0 0 1 1 0  ---- 6
    0 0 0 0 0 0 0 1 0 1  ---- 5
    The "result" of that, according to the bitwise comparison, is
    Code:
                8 4 2 1           
    0 0 0 0 0 0 0 1 0 0
    Any amount of 1s and you get a True, so 5 And 6 is True. ( The actual result of 5 And 6 is what that last binary number is in decimal which is 4, but anything other than 0 is True )

    Do the same for 4And 2 and the result is got from this
    Code:
                8 4 2 1
    0 0 0 0 0 0 0 0 1 0  ---- 2
    0 0 0 0 0 0 0 1 0 0  ---- 4
    , which finally is
    Code:
                8 4 2 1           
    0 0 0 0 0 0 0 0 0 0
    That is 0 in binary or decimal
    https://i.postimg.cc/hvzXKctd/5-And-6-4-And-2.jpg 5 And 6 4 And 2.JPG





    So far so good.
    can take the second small function, Function NumbersInVBAIf_And_Then(ByVal Dec1 As Long, Dec2 As Long) As Boolean , as OK


    Perhaps better said, the final function, Function NumbersInVBAIf_And_Then(ByVal Dec1 As Long, ByVal Dec2 As Long) As Boolean , is also OK. With the right numbers
    There is not much there for it to do wrong: It does a simple job of detecting any position where both decimal numbers have a 1. Simple and correct.

    So what is the damm problem?? I think we know. The original simple Decimal to Binary function got the correct binary number for positive numbers, but usually wrong numbers for the negative as it was not based on the Two's complement codswollop for negative numbers
    So we just need a new function to convert decimals correctly, in the case of negative numbers, in the Two's complement styleo






    Two’s Compliment Function
    There is nothing clever or difficult required. We just need to apply the logic carefully.

    I done a coding quite quick, it won’t be the best, but it will do. 2 main sections, Rem 1, for positive given decimal numbers, Rem 2 for any negative given decimal numbers

    Rem 1 - in the coding
    Positive decimal numbers can be handled as in the main part of the previous simple decimal to binary coding, Function NumberInBinary(ByVal DecNumber As Long) As String
    Code:
    Public Function NumberInBinary2sCompliment(ByVal DecNumber As Long) As String
        If Not DecNumber < 0 Then
        Rem 1 Positive decimal number
         Let NumberInBinary2sCompliment = NumberInBinary2sCompliment & "0" ' The first digit ( or last 32th if you prefer ) is included, 0 is for a positive number
        ' Here we go again with the classic school maths way of converting a decimal number to binary
        Dim N As Long ' N is effectively the power of two at any time
            For N = 30 To 0 Step -1  '  We can think of this as looping from left to right, down the power of 2 values.           30 seems to be the limit before something is too big
                If DecNumber / (2 ^ N) >= 1 Then ' We need a   1   in the position,  for this power of 2
                 Let NumberInBinary2sCompliment = NumberInBinary2sCompliment & "1" ' putting effectively a   1   in the position,  for this power of 2
                 Let DecNumber = DecNumber - (2 ^ N) ' We have effectively accounted for an amount equal to this power of 2, so the decimal number we will further investigate must effectively be reduced
                Else ' We cant effectively eat up am amount from the decimal of this value of power 2 as the decimal total is smaller, so the binary string needs a 0 at this position
                 Let NumberInBinary2sCompliment = NumberInBinary2sCompliment & "0"
                End If
            Next N ' We effectively go to the next power of 2 down
        Exit  Function ' We are finished here for a positive decimal number
        Else ' The case of a negative decimal number
    For the positive number we just divide the decimal number by decreasing powers of 2.
    __ If that gives >= 1 then we add a 1 to the binary number string, effectively then that is at a position for that power of 2. The decimal number is then reduced accordingly by that power of 2 amount.
    __ If that division gave a number less than 1 then a 0 is added to the binary number string
    Then we repeat this for the next power of two down, and so on.
    For our new coding, for this case of a positive number, the function would finally end when all powers of two had been considered

    For the Case of a negative decimal number, its just a case of carefully following the exactly the process of twos compliment in some way

    The following coding description is the first way I came up with, so I doubt it’s the most efficient It will do for now
    I will do that in the next post as its specifically for getting the 2’s compliment and it may be good to have a separate post to reference later


    …. Continued in the next post
    Last edited by DocAElstein; Today at 12:42 AM.

  4. #14
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,455
    Rep Power
    10
    later

Similar Threads

  1. Version Info using VBA and registry quirks
    By DocAElstein in forum Test Area
    Replies: 6
    Last Post: 10-23-2024, 01:50 PM
  2. ADS info via VBA 64bit
    By TML59 in forum Excel Help
    Replies: 9
    Last Post: 07-13-2024, 03:43 PM
  3. Replies: 26
    Last Post: 07-17-2013, 11:42 AM
  4. Info: different Value !
    By PcMax in forum Excel Help
    Replies: 2
    Last Post: 04-22-2012, 04:13 PM
  5. Version 2003 to 2007
    By PcMax in forum Excel Help
    Replies: 5
    Last Post: 11-23-2011, 07:52 PM

Posting Permissions

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