Results 1 to 10 of 14

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

Hybrid View

Previous Post Previous Post   Next Post Next Post
  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,455
    Rep Power
    10
    2’s Compliment Function Decimal To Binary conversion of negative Decimal numbers

    '== Rem 2 == 2's complement Negative Binary number from decimal ===============================
    The coding is not written particularly efficient. It’s written in a way to help understand more clearly what is going on for learning purposes and better later revision
    '2a) I see no fundamental reason not to work on the negative decimal number, but for clarity I make the decimal number to its absolute (positive) value here. (A sign change would do just as well here)
    '2b) This section is once again possibly an inefficient thing to do, but for clarity, I find the power of 2 number ( value of N ) at which (2 ^ N) is equal or bigger than the (now considered as positive) decimal number . In effect we know the position where in simple normal binary the first 1 would go looking left to right, in other words we effectively have this value considering normal binary values
    9 8 7 6 5 4 3 2 1 0 ---- N
    0 0 0 1 1 0 1 1 0 0 ---- Normal binary number
    For the above example, I am saying we are at the left first digit of a final binary number that , as example, would look in normal binary as this
    1 1 0 1 1 0 0
    '2c) This section is just the classic school maths of converting a decimal to a binary, just back to front with a 0 put where you would put a 1 and visa versa. This is because, considering the last example again, we want to have the flip of that, so we actually want
    0 0 1 0 0 1 1
    '2c)(i) Using the above example again, I am at the start of constructing the string variable to be returned by the function, NumberInBinary2sCompliment, or rather , at the first significant part, effectively what would be the first 1 in normal binary. But, in actual fact, I want the "flip" of it. Rather than construct it and then flip it, which would be talking inefficiency a bit far, I construct it on the flip side as it where. So I add my first character to the string. It will be the flip of 1, so it will be 0
    '2c)(ii)The first binary digit was known so added above, as was the reduction of the decimal value by the (2 ^ N) value. So now we continue the looping for the rest
    I am using a Do While Loop for no particular reason, rather than a For Next Loop, - its just slightly simpler than having to have a variable, such as NN for the next N to use in a line like For N = NN To 0 Step -1 . But basically I do now the classic progression in school maths, just back to front(flipped), i.e., with a 0 put where you would put a 1 and visa versa
    So at the end of this section I have my final flipped binary number for the decimal value. In other words I have the exact flip of the normal binary for the decimal number.
    '2d) I have the flip, so I now want to add a 1 in binary
    I loop, effectively going from right to left along the binary number. because of the way I add a 1 in binary, I effectively am looking for the next " empty" , that is to say 0 , in which to "dump" this 1. If I find a 1, I must change that 1 to a 0, and try again at the next left position. I am finished in this For Next loop as soon as I have "got rid" of the 1
    At this point I sort of, have my final 2s Compliment binary number. But generally, a binary in computer workings has a fixed length , so the a normal number would have a lot of 0s added to the left, or as many as needed to get the length, probably 32 I would guess. In this negative value 2s compliment, the basic idea is the same, except that 1s are added to the left.
    '2e)
    _ I make a variable of the length finally wanted. (The characters I use is irrelevant!!°)
    _ The RSet statement puts my current 2s compliment binary number at the right of the made string, ( and the rest of the characters become spaces, hence the characters I used to make the string was irrelevant!!° )
    _ The spaces are changed to 1s



    That’s it!

    Code:
    '   https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API?p=24922&viewfull=1#post24922
    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
    '== Rem 2 == 2's 2's complement Negative Binary number from decimal  ===============================
        '2a)
         Let DecNumber = Abs(DecNumber) ' We know we are negative, that will be taken care of automatically later as a result of making all unused digits 1.  I could probably fiddle the maths below to work on negative numbers, but just for lazy comvenmience I will make the decimal number positive here
        '2b) This bit brings me
         Let N = 30 ' Back to the start left of our powers of 2
        Dim Frac As Double: Let Frac = DecNumber / (2 ^ N)
            Do While Frac < 1 ' We want to get to the number of digits needed for the number when in normal binary representation. Mostly lazy convenience I think so as to see  a nice smaller amount of 0s and 1s when testing/ debugging
             Let N = N - 1
             Let Frac = DecNumber / (2 ^ N)
            Loop '  While Frac < 1  ' I am effectibely working from left to right along the power to 2 range,
         '2c) The classic school maths of converting a decimal to a binary, just back to front (fliped) with a 0 put where you would put a 1 and visa versa
         '2c)(i) In normal binary I know I want my first 1,
         Let NumberInBinary2sCompliment = "0" ' so we have as many digits as we need and we know the first digit would be 1 in binary , but in 2sCompliment it will be  "0"
         Let DecNumber = DecNumber - (2 ^ N)  ' this and the last line are effectively the first use of the  If  section in the school maths way of converting a decimal to a binary
         '2c)(ii)
            Do While N <> 0
             Let N = N - 1
                If DecNumber / (2 ^ N) >= 1 Then ' The next 3 code lines are the classic progression in school maths, just back to front(flipped) with a 0 put where you would put a 1 and visa versa
                 Let NumberInBinary2sCompliment = NumberInBinary2sCompliment & "0"
                 Let DecNumber = DecNumber - (2 ^ N)
                Else
                 Let NumberInBinary2sCompliment = NumberInBinary2sCompliment & "1"
                End If
            Loop ' While N <> 0
        '2d) add 1 in binary maths
        Dim ToAdd As Long: Let ToAdd = 1 ' I have 1 and I need to get rid of it. (##I don't need the variable, I could use just a 1 in place of it) I work from the right of the binary number and effectively dump it on the first position with a 0   If the positon is 1 already, I must changer that to 0 , - a bit like reaching 10 in normal maths, where you leave aa 0 then carry the 1 over to the next column/digit on the left, then try again to get rid of the 1
            For N = Len(NumberInBinary2sCompliment) To 1 Step -1 ' Effectively going from right to left along the binary number
                If Mid(NumberInBinary2sCompliment, N, 1) = 0 Then ' I can dump my 1 here then i am finished with this section
                 Mid(NumberInBinary2sCompliment, N, 1) = ToAdd   '                ##I don't need the variable, I could use just a 1 in place of it
                 Let ToAdd = 0 ' I don't need this as I am finished here.
                Exit For ' As soon as we got rid of the 1 to add, we are finished
                Else ' I must have come acros a 1
                 Mid(NumberInBinary2sCompliment, N, 1) = 0 ' I hit a 1, so 1+1 in binary is like reaching reaching 10 in normal maths, where you leave aa 0 then carry the 1 over to the next column/digit on the left, then try again to get rid of the 1
                End If
            Next N ' Go to next character to the left to see if it is 0 so that I can get rid of the 1 ToAdd
        '2e) ' my final binary number could be short or long at this point depending on the size of the originbal decimal number. This ssection
        Dim BiffaBin As String: Let BiffaBin = String$(32, " ") ' Make a string of the length I want, (The characters I use is irrelevant!!)
         RSet BiffaBin = NumberInBinary2sCompliment ' The RSet statement puts my current 2s compliment binary number at the right of the made string, ( and the rest of the characters become spaces, hence the characters I used to make the string was irrelevant!! )
         Let NumberInBinary2sCompliment = Replace(BiffaBin, " ", "1", 1, -1, vbBinaryCompare) '
        End If
    End Function
    Last edited by DocAElstein; Today at 04:05 AM.

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
  •