Announcement

Collapse
No announcement yet.

Re: PB's Gazette #59

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Re: PB's Gazette #59

    When I get a gazette issue, I usually store it and may look at it later. However, #59 kinda caught my eye this time. Specifically the bit field variable.

    I sometimes program with a syntax something like:
    Code:
    global FlagByte as string
    
    function pbmain()
    
    FlagByte = string$(8,"0")                 ' A full byte
    
    ...process
    ...process
    
    if x = y then mid$(FlagByte,4,1) = "1"
    
    ...process
    ...process
    
    if mid$(FlagByte,6,1) = "1" then
    DoSomething
    else
    DoSomethingElse
    end if
    
    ...process
    ...process
    
    end function
    FlagByte can easily be converted to a CHR$() and stored on disk.

    Since I can't get a full grip on how it's used, can somebody "translate" the above to use a bit field variable? Sounds like it's far faster and more efficient than my way of doing it.
    There are no atheists in a fox hole or the morning of a math test.
    If my flag offends you, I'll help you pack.

  • #2
    Hi Mel,

    here are two ways:
    Using BIT statement and function
    Code:
    #COMPILE EXE
    
    MACRO DoSomething     = MSGBOX "Doing something"
    MACRO DoSomethingElse = MSGBOX "Doing something ... ELSE !"
    
    FUNCTION PBMAIN()
    
      LOCAL FlagByte AS BYTE
      LOCAL x, y AS LONG
      '...process
      '...process
    
      ' -- bits are numbered 0..7, thats why 3 for 4th
      IF x = y THEN BIT SET FlagByte, 3
    
      ' -- bits are numbered 0..7, thats why 5 for 6th
      ' -- Uncomment following to finally DoSomething :)
      'BIT SET FlagByte, 5
    
      IF BIT(FlagByte, 5) THEN
        DoSomething
      ELSE
        DoSomethingElse
      END IF
    
      '...process
      '...process
    
    END FUNCTION
    Using Gazette engine
    Code:
    [COLOR="Red"]' Corrected thanks to Frank W. Kelley[/COLOR]
    #COMPILE EXE
    
    TYPE TFlag8
      a   AS BIT * 1 IN BYTE
      b   AS BIT * 1 
      c   AS BIT * 1 
      d   AS BIT * 1 
      e   AS BIT * 1 
      f   AS BIT * 1 
      g   AS BIT * 1
      h   AS BIT * 1
    END TYPE
      
    
    MACRO DoSomething     = MSGBOX "Doing something"
    MACRO DoSomethingElse = MSGBOX "Doing something ... ELSE !"
    
    FUNCTION PBMAIN()
    
      LOCAL FlagByte AS TFlag8
      LOCAL x, y AS LONG
      '...process
      '...process
    
      IF x = y THEN FlagByte.d = 1
    
      ' -- Uncomment following to finally DoSomething :)
      'FlagByte.e = 1
      IF FlagByte.e = 1 THEN
        DoSomething
      ELSE
        DoSomethingElse
      END IF
    
      '...process
      '...process
    
    END FUNCTION
    At least I understood latest Gazette this way, but seems to work.


    Bye,
    Petr

    EDIT: Corrected first example
    Last edited by Petr Schreiber jr; 10 Mar 2008, 09:58 AM.
    [email protected]

    Comment


    • #3
      I use this feature a lot. However, I believe the proper use is:

      Code:
      TYPE TFlag8
        a   AS BIT * 1 IN BYTE
        b   AS BIT * 1
        c   AS BIT * 1
        d   AS BIT * 1
        e   AS BIT * 1
        f   AS BIT * 1 
        g   AS BIT * 1
        h   AS BIT * 1
      END TYPE
      The first "IN BYTE" defines the size of the variable (in this case giving you eight bits to play with). The original example posted above actually defines eight different bytes, and using only the first bit of each of them. To add additional bit storage beyond eight, you can use another BYTE, as in:

      Code:
      TYPE TFlag8
        a  AS BIT * 1 IN BYTE
        b  AS BIT * 1
        c  AS BIT * 1
        d  AS BIT * 1
        e  AS BIT * 1
        f  AS BIT * 1 
        g  AS BIT * 1
        h  AS BIT * 1
        i  AS BIT * 1 IN BYTE  ' <-- new BYTE boundary starts here
        j  as BIT * 1
      END TYPE
      ...or use DWORD for a total of four bytes (32 bit flags).

      Be very careful not to exceed the size of the allocated space. Adding a ninth bit to a byte in your UDT produces the proverbial "unpredictable results".
      --
      <strong>Billing clients for your freelance work?</strong> Try <a href="http://www.minute-2-minute.com">Minute-2-Minute</a>, the project management, timing, and billing system. Perfect for programmers who charge by the hour. FREE 45-day trial.

      Comment


      • #4
        Thanks for the correction,


        Petr
        [email protected]

        Comment


        • #5
          Here is an example with timings from my (slow) laptop of various flag techniques. Relative times, however, should be similar for most machines. The flagArr() example would allow a numeric variable for the flag indexes as would your $MID statement.

          Code:
          #COMPILE EXE
          #DIM ALL
          #INCLUDE "win32api.inc"
          
          TYPE TFlag8
            a   AS BIT * 1 IN BYTE
            b   AS BIT * 1
            c   AS BIT * 1
            d   AS BIT * 1
            e   AS BIT * 1
            f   AS BIT * 1
            g   AS BIT * 1
            h   AS BIT * 1
          END TYPE
          
          TYPE strFlag
             a AS BYTE
             b AS BYTE
             c AS BYTE
             d AS BYTE
             e AS BYTE
             f AS BYTE
             g AS BYTE
             h AS BYTE
          END TYPE
          
          FUNCTION PBMAIN () AS LONG
             LOCAL typeByt AS TFlag8, typeStr AS strFlag
             LOCAL ii, f1 AS LONG
             LOCAL q1, q2 AS QUAD
             LOCAL flagQuad AS STRING          'as Frank prev. said, it's 8 bytes, called "Quad" here. But actual bits used = &b110001 (= "1")
             DIM flagArr(8) AS LONG
                 queryPerformanceCounter q1    'uncomment one example below at a time to test each yourself.
                 FOR ii = 1 TO 100000000       '571000   base loop speed in ~ µsec
          '         f1        = 1              '850000   net = 279K         ~ µsec  = nominal ref. speed
          '         typeStr.c = &h31 '"1"      '854000   net = 283K            "    = ~ nominal
          '         flagArr(2)= &h31           '1410000  net = 839K            "    = 3   x slower
          '         typeByt.a = 1              '3370000  net = 2799K        ~ µsec  = 10  x slower
          '         mid$(flagQuad, 3, 1) = "1" '36600000 net = 36029K          "    = 129 x slower
                 NEXT
                 queryPerformanceCounter q2
                 ? STR$(q2 - q1)
          
          END FUNCTION

          Comment


          • #6
            If you are not comfy with the Boolean operators (AND, OR, NOT, XOR, IMP) using bit datatypes ("In DWORD") might be a more intuitive way to query and/or set various bit flags.
            Michael Mattias
            Tal Systems (retired)
            Port Washington WI USA
            [email protected]
            http://www.talsystems.com

            Comment


            • #7
              I like the syntax of:

              IF FlagByte.e = 1 THEN ...

              Slice of pie to remember. I'm going to print out this entire thread and save it for future reference.
              There are no atheists in a fox hole or the morning of a math test.
              If my flag offends you, I'll help you pack.

              Comment


              • #8
                Here is a titbit which may come in handy - not often I should imagine.

                I'm looking at an algorithm which builds a binary string from nybbles got from a substitution box in cryptography.

                Code:
                Type TwoNybbles
                  LowerNybble As Bit * 4 In Byte
                  UpperNybble As Bit * 4
                End Type
                
                Union NybbleWorks
                  BothNybbles As Byte
                  AByte As TwoNybbles
                End Union
                
                Macro PutXNybble(prm1,prm2) = X.AByte.prm1 = prm2
                Macro GetXByte = X.BothNybbles
                
                Function PBMain( ) As Long
                
                  Dim X As NybbleWorks
                    
                  PutXNybble(UpperNybble, 12 )
                  PutXNybble(LowerNybble, 9 )
                
                  ? Str$(GetXByte) + " " + Bin$(GetXByte)
                
                END FUNCTION

                Comment


                • #9
                  Dave, here's a comparison doing the substitution box using pointers too. It's less code and it clocks about 45-50% faster.
                  Code:
                  #COMPILE EXE
                  #DIM ALL
                  DECLARE FUNCTION QueryPerformanceCounter LIB "KERNEL32.DLL" ALIAS "QueryPerformanceCounter" (lpPerformanceCount AS QUAD) AS LONG
                  
                  TYPE TwoNybbles
                    LowerNybble AS BIT * 4 IN BYTE
                    UpperNybble AS BIT * 4
                  END TYPE
                  
                  UNION NybbleWorks
                    BothNybbles AS BYTE
                    AByte AS TwoNybbles
                  END UNION
                  
                  MACRO PutXNybble(prm1,prm2) = X.AByte.prm1 = prm2
                  MACRO GetXByte = X.BothNybbles
                  
                  FUNCTION cryptWithTypeUnion () AS LONG
                  
                    DIM X AS NybbleWorks
                    LOCAL ii, ii2, y AS LONG, q1, q2 AS QUAD
                    DIM cryptBox(255) AS BYTE
                  
                      queryPerformanceCounter q1
                      FOR ii2 = 1 TO 100000
                      FOR ii = 1 TO 256
                         y = ii AND &h0f
                         PutXNybble(LowerNybble, y )
                         y = ii + 1 AND &h0f
                         PutXNybble(UpperNybble, y )
                         cryptBox(ii - 1) = getXbyte
                  '       ? str$(cryptBox(ii - 1))
                      NEXT
                      NEXT
                      queryPerformanceCounter q2
                      ? STR$(q2 - q1) & " = TYPE/UNION time"
                      FUNCTION = q2 - q1
                  
                  END FUNCTION
                  
                  FUNCTION cryptWithPtrs () AS LONG
                  
                      DIM cryptBox(255) AS BYTE
                      LOCAL cbPtr AS BYTE PTR
                      LOCAL ii, ii2, y AS LONG, q1, q2 AS QUAD
                  
                      queryPerformanceCounter q1
                      FOR ii2 = 1 TO 100000
                      cbPtr = VARPTR(cryptBox(0))
                      FOR ii = 1 TO 256
                         y = ii AND &h0f
                         @cbPtr = y
                         y = ii + 1 AND &h0f
                         @cbPtr = @cbPtr + y * 16           'y * 16 = SHIFT LEFT, y, 4. This moves its bits to high nybble
                  '       ? STR$(@cbPtr)
                         INCR cbPtr
                      NEXT
                      NEXT
                      queryPerformanceCounter q2
                      ? STR$(q2 - q1) & " = POINTER time"
                      FUNCTION = q2 - q1
                  
                  END FUNCTION
                  
                  FUNCTION PBMAIN ( ) AS LONG
                     ? "The pointer method was " & FORMAT$((cryptWithTypeUnion / cryptWithPtrs - 1) * 100, "0.00") & "% faster."
                  END FUNCTION

                  Comment


                  • #10
                    Hi John

                    My original code was very specific and used assembly language. The relative overhead was so negligible that I could have used vbscript with an almost unmeasurable performance loss. It played a part in a function which itself only took 0.04ms regardless of the size of the message. To reuse the code in six months time may see me scratching my head. On the other hand, if I couldn't figure out what PutXNybble(UpperNybble, y ) meant then I may as well give up.

                    Union NybbleWorks could be dropped into any piece of code with hardly any thought. Having got the whole code working if it transpired that it was time critical then I'd scratch my head and replace it with assembly - I wouldn't bother with variants of PB code.
                    Last edited by David Roberts; 11 Mar 2008, 04:04 PM. Reason: Replaced 'without' with 'with' <smile>

                    Comment


                    • #11
                      Code:
                      It played a part in a function which itself only took 0.04ms regardless of the size of the message.
                      Ah yes, I see now. It probably should have dawned on me that 1) the substitution box(es) are calculated only once per run, (for some reason I was thinking, "You want that as fast as possible since it's in the innermost loop"), 2) you wanted to demo the bit field variables, and finally 3) if you need max speed, you'll program it in there.

                      Side note: Oof again, I noticed pointers aren't even needed in my code above. The array elements can be used simply as is:
                      Code:
                          FOR ii = 0 TO 255
                             y = ii + 1 AND &h0f
                             cryptBox(ii) = y 
                             y = ii + 2 AND &h0f
                             cryptBox(ii) = cryptBox(ii) + y * 16     'moves bits to high nybble
                          NEXT

                      Comment


                      • #12
                        >moves bits to high nybble

                        Code:
                         LOCAL Z AS BYTE
                        
                         Z = &h0F?                ' Z = &b00001111
                         SHIFT LEFT Z, 4        ' Z = &b11110000
                        Michael Mattias
                        Tal Systems (retired)
                        Port Washington WI USA
                        [email protected]
                        http://www.talsystems.com

                        Comment


                        • #13
                          That is what my assembly was doing.

                          Code:
                          Macro BuildByte( row0, col0, row1, col1)
                          ' Put row0/col0 into upper nybble & row1/col1 into lower nybble of result
                          
                            ! mov esi, row0
                            ! mov ebx, col0
                            ! mov al, Byte Ptr [esi + ebx]
                            ! shl al, 4                        ' [B]shift left 4 bits[/B]
                            ! mov esi, row1
                            ! mov ebx, col1
                            ! mov bl, Byte Ptr [esi + ebx]
                            ! Add al, bl
                            ! mov result, al ' result available to BASIC
                          End Macro
                          where row? and col? correspond to the substitution box, a 2*n table. I'm still working on n.

                          Comment


                          • #14
                            > Put row0/col0 into upper nybble & row1/col1 into lower nybble of result

                            You must be really good.

                            I wouldn't even try to squeeze 4 nibbles @ 4 bits each into an 8-bit register.

                            Regardless, here's some code where I used the PB intrinsics to do pretty much the same thing, except my target variable was big enough for what I wanted to put in it:

                            http://www.powerbasic.com/support/pb...ad.php?t=25176 (post #2)
                            Michael Mattias
                            Tal Systems (retired)
                            Port Washington WI USA
                            [email protected]
                            http://www.talsystems.com

                            Comment


                            • #15
                              Just posted over in Source Code a little demo of how I use a bit field type variable within our Timber Sale System here in the PA Bureau of Forestry. The post is at…




                              I created the system before PowerBASIC came out with its bit field variables, so unfortunately, they are not used in this demo. However, the demo does show how bit fields can be tied to an array of check boxes on a Form/Dialog that presents users with a visually rich picture of the status of a particular timber sale. This technique could be used for nearly anything, only being limited by the imagination of the programmer. In our timber sale system we have 22 ‘states’ which can describe the present status of a timber sale. These are all True/False states. They are as follows:

                              Received Timber Sale Proposal
                              Sent Sale Approval To District
                              Received Timber Sale Data
                              Processed Timber Sale
                              Draft Prospectus Done
                              Prospectus Mailed To Buyers
                              Sale Awarded
                              No Bid Sale
                              Approved To Negotiate No-Bid
                              Sent Contract To Buyer
                              Received Contract From Buyer
                              Sent Contract To Legal
                              Received Contract From Legal
                              Contract Executed
                              Sent Perf. Dep. To Comptroller.
                              Sale Activated (1st Block Paid)
                              Received FMT-9 From District Forester
                              Sale Terminated
                              Request Comptroller For Perf. Dep.
                              Returned Performance Deposit
                              Withheld Perf. Deposit.
                              State Park Sale

                              We have about 150 timber sales/year let out on contracts ranging from 1 to 3 years usually, so at any given time we have piles of timber sales in many different states to keep track of. This system has worked very well for us. The status field is tied to a 32 bit integer in the database’s main table. The system has proven easy to update too. After the system had been written my boss asked that another field be added to the array of check boxes, that is the “State Park Sale” item. It is important for us to differentiate this as we use a very complex procedure to determine our allowable cut acres for each year, and sales we do for the State Park folks aren’t included in those acreages. As things stand now we still have ten bits left in the 32 bit field for future expansion if necessary.

                              I see no reason why this technique wouldn’t be applicable to many fields. For example, if you write programs to help Motel managers keep track of their rooms, I suppose you could specify a bit for whether or not a particular room had a double bed or a queen sized bed, whether it had an ironing board or not, and so on.

                              Unfortunately, I only do Sdk, and there probably isn’t anything here Sdk coders aren’t familiar with. If my demo has merit, perhaps some enterprising coder might convert it to DDT?

                              Also, the demo shows how to handle WM_CTLCOLORSTATIC messages for some extra colors I associated with several of the check boxes to denote especially important items in our scheme of things, and also to add a little color to the Form/Dialog.
                              Fred
                              "fharris"+Chr$(64)+"evenlink"+Chr$(46)+"com"

                              Comment


                              • #16
                                > I wouldn't even try to squeeze 4 nibbles @ 4 bits each into an 8-bit register.

                                "I'm looking at an algorithm which builds a binary string from nybbles got from a substitution box in cryptography." from post #8.

                                row0/col0 points to a nybble in a table
                                row1/col1 points to a nybble in a table

                                That is two nybbles into a byte.

                                Didn't think I'd have to spell it out.

                                Comment


                                • #17
                                  >That is two nybbles into a byte

                                  Well, that's a horse of a different color. And as far as spelling, I thought "nybbles" was just an alternate spelling for "nibbles."

                                  But now that we now that a 'nybble' is but two bits....

                                  Code:
                                  TYPE BYteVar
                                     RowO  AS BIT * 2 IN BYTE
                                     Col0  AS BIT * 2
                                     Row1  AS BIT * 2 
                                     Col1  AS BIT * 2 
                                  END TYPE 
                                  
                                  FUNCTION BuildByte (row0 AS BYTE, col0 AS BYTE, row1 AS BYTE, col1 AS BYTE) AS BYTE
                                  
                                    LOCAL Z AS BYteVar, pB AS BYTE PTR
                                  
                                    Z.Row0   = Row0
                                    Z.Col0   = Col0
                                    Z.Row1   = Row1
                                    Z.Col1   = Col1
                                    pB       = VARPTR (Z)
                                  
                                    FUNCTION = @pB
                                  
                                  END FUNCTION
                                  OR
                                  Code:
                                  FUNCTION BuildBYte (row0 AS BYTE, col0 AS BYTE, row1 AS BYTE, col1 AS BYTE) AS BYTE
                                  
                                    LOCAL Z AS BYTE 
                                    Z         = Row0
                                    SHIFT LEFT  Z, 6
                                    Z = Z  OR (col0 * &b10000?) OR (row1 * &b100?) OR Col1 
                                  
                                    FUNCTION = Z 
                                  
                                  END FUNCTION

                                  MCM
                                  Michael Mattias
                                  Tal Systems (retired)
                                  Port Washington WI USA
                                  [email protected]
                                  http://www.talsystems.com

                                  Comment


                                  • #18
                                    > But now that we now that a 'nybble' is but two bits....

                                    WHAT?

                                    row?/col? is a pair. It doesn't matter whether row? is a single bit, a byte, a dword or anything else. Similarly with col?. They simply point to a nybble. In the context of the code that I am working on, row? is a bit and col? is two bits, but that is academic.

                                    > And as far as spelling, I thought "nybbles" was just an alternate spelling for "nibbles."

                                    No.

                                    Comment


                                    • #19
                                      Ok, OK: I'll quit while I'm ahead!
                                      Michael Mattias
                                      Tal Systems (retired)
                                      Port Washington WI USA
                                      [email protected]
                                      http://www.talsystems.com

                                      Comment

                                      Working...
                                      X