Tetris is the hottest new puzzle game right now. Needless to say, everyone wants a piece of it (pun very much intended.) The game's title comes from the word "Tetromino," a geometric shape composed of four squares connected orthogonally. The game features seven unique pieces in the shape of O, I, S, Z, L, J and T. Each piece can fit a 4x4 grid:

The goal is to place tetrominoes in a well, organizing them into complete rows, which then disappear. If the stack reaches the top of the field, it's game over.

Block data

Since all pieces fit a 4x4 grid, and each cell is either solid or empty, we only need one 16-bit INTEGER per pattern. In binary form, 16-bit INTEGERs look as follows (the most significant bit is located to the left and the least significant bit to the right:)

bit 15 14 13 12 11 10 09 08 07 06 05 04 03 02 01 00   dec
     0  0  0  0  0  0  0  0  0  0  0  0  0  0  0  0 = 0
     0  0  0  0  0  0  0  0  0  0  0  0  0  0  0  1 = 1   (2^0)
     0  0  0  0  0  0  0  0  0  0  0  0  0  0  1  0 = 2   (2^1)
     0  0  0  0  0  0  0  0  0  0  0  0  0  0  1  1 = 3   (2^0 + 2^1)
     0  0  0  0  0  0  0  0  0  0  0  0  0  1  0  0 = 4   (2^2)
     0  0  0  0  0  0  0  0  1  0  0  0  1  0  0  1 = 137 (2^0 + 2^3 + 2^7)
etc.

Instead of seeing 16-bit integers as one string of sixteen cells, we may display them as grids of 4 lines and 4 columns, starting with the four most significant bits (top row) and ending with the four least significant bits (bottom row.) In that representation, the most significant bit (2^15, or 32,768 in decimal) will be in the top left cell, and the least significant bit (2^0, or 1 in decimal) in the bottom right cell (this cell is also the origin point for the block.) When a cell is solid, the matching bit is set. If the cell is empty, the bit is clear:

Note that in the hexadecimal representation, each character (right to left) represents a line (bottom to top.) It's not very important, but it can help visualize what's going on internally.

Some pieces have four different orientations (L, J and T,) others only two (I, S and Z,) and O doesn't really rotate at all. To keep things simple, we're going to assume they all have four rotations (although some will be repeats.) Each piece is thus defined using only four 16-bit integers (8 bytes of memory:)

The following code snippet shows how to store and decode blocks, as well as perform rotations and find the pattern currently in use:

' Basic operations
DIM pattern(0 TO 27) AS INTEGER       ' Patterns (rotated blocks)
DIM plBlk AS INTEGER                  ' Player block index, 0 to 6
DIM plRot AS INTEGER                  ' Player block orientation, 0 to 3
DIM plPat AS INTEGER                  ' Actual pattern code

' Initialize randomizer
RANDOMIZE TIMER

' Decode DATA statements
FOR i% = 0 TO 27
  READ s$
  pattern(i%) = VAL("&h" + s$)
NEXT i%

' Select block randomly
plBlk = INT(RND * 7)

' Rotate
plRot = (plRot + 1) AND &h3 ' Clockwise
plRot = (plRot + 3) AND &h3 ' Counter-clockwise

' Pattern code
plPat = pattern((plBlk * 4) + plRot)

' 7 blocks x 4 orientations = 28 patterns (hexadecimal)
DATA 0660,0660,0660,0660
DATA 2222,0F00,2222,0F00
DATA 0360,4620,0360,4620
DATA 0630,2640,0630,2640
DATA 4460,0740,0622,02E0
DATA 2260,0470,0644,0E20
DATA 0270,0464,0E40,2620

Bit manipulation

Memory-efficiency aside, using 16-bit integers also makes simple math and boolean operators very convenient manipulation tools. For instance we can isolate the top row of a pattern by creating a mask. We first set a variable to 61,440 (or &hF000 in hexadecimal,) and use it in conjunction with the AND boolean operator and a pattern:

It is also possible to shift patterns to the left or right by simply dividing or multiplying by a power of two. For instance, performing an integer division by 2 will shift bits to the right once, dividing by 4 will shift bits to the right twice:

         24 = 0 0 0 0 0 0 0 0 0 0 0 1 1 0 0 0
24 \ 2 = 12 = 0 0 0 0 0 0 0 0 0 0 0 0 1 1 0 0
24 \ 4 =  6 = 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 0
etc.

And of course, we can also shift bits to the left:

          8 = 0 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0
 8 * 2 = 16 = 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0
 8 * 4 = 32 = 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0 0
etc.

In theory, using divisions and multiplications to perform bit shifting works, but only on UNSIGNED integers, which QuickBASIC doesn't support. In fact, this method will break on negative integers (that is, when the most significant bit is set) or when the absolute value reaches 32,768.

The simplest way to solve the issue would be to use 32-bit integers. Alternatively, we may rebuild SHL ("<<") and SHR (">>",) two bitwise operators found in C. Our function would discard the most significant bit before shifting and restore it at the end of the operation:

DEFINT A-Z

DECLARE FUNCTION SHR% (i AS INTEGER, b AS INTEGER)
DECLARE FUNCTION SHL% (i AS INTEGER, b AS INTEGER)
DECLARE FUNCTION BIN$ (i AS INTEGER)

CLS

v% = &HE187
PRINT "INIT.  "; BIN$(v%); " "; v%

' Shift bits left and right
LOCATE 3
FOR i% = 0 TO 16
  PRINT "SHL"; i%; TAB(8); BIN$(SHL%(v%, i%)); " "; SHL%(v%, i%); TAB(40);
  PRINT "SHR"; i%; TAB(47); BIN$(SHR%(v%, i%)); " "; SHR%(v%, i%)
NEXT i%

''
'' Displays integer (16 bits) in binary form, most significant bit first
''
FUNCTION BIN$ (i AS INTEGER)
  t$ = STRING$(16, "0")
  FOR b% = 0 TO 15
    IF (i AND (2 ^ b%)) THEN MID$(t$, 16 - b%, 1) = "1"
  NEXT b%
  BIN$ = t$
END FUNCTION

''
'' Shift Bits Left
''
FUNCTION SHL% (i AS INTEGER, b AS INTEGER)
  DIM s AS INTEGER

  SELECT CASE b
  CASE IS < 1
    SHL% = i
  CASE IS > 15
    SHL% = 0
  CASE ELSE
    s = (2 ^ (15 - b))
    IF (i AND s) THEN
      SHL% = (i AND (s - 1)) * (2 ^ b) OR &H8000
    ELSE
      SHL% = (i AND (s - 1)) * (2 ^ b)
    END IF
  END SELECT
END FUNCTION

''
'' Shift Bits Right
''
FUNCTION SHR% (i AS INTEGER, b AS INTEGER)
  SELECT CASE b
  CASE IS < 1
    SHR% = i
  CASE IS > 15
    SHR% = 0
  CASE ELSE
    IF (i AND &H8000) THEN
      SHR% = ((i XOR &H8000) \ (2 ^ b)) OR (2 ^ (15 - b))
    ELSE
      SHR% = i \ (2 ^ b)
    END IF
  END SELECT
END FUNCTION

Collisions

Like patterns, the board is stored in an array of 16-bit integers. Each element of the array contains a 16-column row, which is more than enough. The length of the array defines the height of the board.

DIM SHARED grid(0 TO 22) AS INTEGER   ' Game board, 23 rows
DIM plX AS INTEGER, plY AS INTEGER    ' Player block coordinates

Remember that the least significant bit (smallest value) is written to the right, and most significant bit (biggest value) to the left. However, this goes against the default graphic coordinates where the leftmost column is index 1 and the rightmost column is index 80. Therefore, plX (the horizontal position of the block) should be reversed when testing for collisions. The illustrations below assume that X is 3 units away from the RIGHT border, Y is 6 units from the top. To keep things sane, entries in the grid() array follow the screen coordinates logic: 0 is top and 22 is bottom. The origin point of the block in the bottom right corner.

Now that we know about masking and bitshifting, we have everything we need to test for collisions. Basically, we'll do exactly what we've being doing above to obtain a 4x4 window of the game board, then we mask the block value with the window value to determine potential collisions:

If the result is 0 then no collision happened. If the result is anything else, then at least one solid cell from the window overlaps a solid cell from the block, therefore the move is invalid. Collision tests should be made ahead to confirm (or cancel) horizontal and vertical moves.

' Test collision
IF (moveValid%(plX, plY, plPat)) THEN
  PRINT "Can move to "; plX; " "; plY
ELSE
  PRINT "Cannot move to "; plX; " "; plY
END IF

''
'' Returns true if pattern P located at X, Y is not colliding
'' with the game board.
''
FUNCTION moveValid% (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM w AS INTEGER, x2 AS INTEGER

  ' Invert horizontal axis
  x2 = 15 - x

  ' Get 4x4 window
  w = ((SHL%((SHR%(grid(y - 3), x2) AND &HF), 12)) OR _
      (SHL%((SHR%(grid(y - 2), x2) AND &HF), 8)) OR _
      (SHL%((SHR%(grid(y - 1), x2) AND &HF), 4)) OR _
      ((SHR%(grid(y), x2) AND &HF)))

  ' Return collision status
  moveValid% = ((w AND p) = 0)
END FUNCTION

To prevent breaking boundaries, padding cells should be added to the board. Three columns on both sides (that leaves ten columns for gameplay) and three bottom lines should be enough. These padding cells shouldn't be displayed on screen.

' Place 6 padding columns (3 on either side) and 3 padding rows.
FOR i = 0 TO 19
  grid(i) = &HE007
NEXT i
grid(20) = &HFFFF
grid(21) = &HFFFF
grid(22) = &HFFFF

Merging blocks, clearing rows

If a block collides while going down, it has landed and should be merged with the board. The OR boolean operator is perfect for this task as it preserves all bits that are set:

Rather than shift the game board left and right, we're going to focus on the pattern value this time and do the complete opposite. First, we isolate each row. Then, we shift the bits of each value left to align with plX. Finally we merge each shifted row with the corresponding board line.

The illustration above shows how to break the pattern value into four distinct rows, the code below goes further by aligning each row to the plX position (remember plX must be reversed so it becomes relative to the right edge rather than the left edge,) and the board merge with the OR boolean operator:

''
'' Merge pattern P in game board at X, Y.
''
SUB blockMerge (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM x2 AS INTEGER

  ' Invert horizontal axis
  x2 = 15 - x

  ' Place piece
  grid(y - 3) = grid(y - 3) OR SHL%((SHR%(p, 12) AND &HF), x2)
  grid(y - 2) = grid(y - 2) OR SHL%((SHR%(p, 8) AND &HF), x2)
  grid(y - 1) = grid(y - 1) OR SHL%((SHR%(p, 4) AND &HF), x2)
  grid(y) = grid(y) OR SHL%(p AND &HF, x2)
END SUB

When the block is placed, we look for (and crush) completed rows (those whose value is &hFFFF,) starting down and going up. The three padding rows (22, 21, and 20) are ignored for the whole process.

''
'' Clear rows
''
SUB clearRow
  DIM count AS INTEGER, i AS INTEGER, j AS INTEGER

  ' Count completed lines (ignore bottom padding)
  FOR i = 19 TO 0 STEP -1
    count = count - (grid(i) = &HFFFF)
  NEXT i

  ' No row completed
  IF (count = 0) THEN EXIT SUB

  ' Search for complete rows
  FOR i = 19 TO 1 STEP -1
    ' This row is complete
    IF (grid(i) = &HFFFF) THEN
      ' Search for next potential incomplete row
      FOR j = i - 1 TO 0 STEP -1
        ' This row is incomplete
        IF (grid(j) <> &HFFFF) THEN
          ' Make complete row swallow incomplete row
          grid(i) = grid(j)
          grid(j) = &HFFFF
          EXIT FOR
        END IF
      NEXT j
    END IF
  NEXT i

  ' Clear top rows (restore left and right padding columns)
  FOR i = 0 TO count - 1
    grid(i) = &HE007
  NEXT i
END SUB

And that's it. Now we give the player another block, reset plX and plY coordinates, and give back control to the player. Test for collision as soon as a new block is given to make sure the player can actually do something. If the block is colliding right away, the game is over.

Rendering

There's no need for amazing graphics, so we'll just stick to the good old 80-columns-by-25-lines text mode. To maintain square aspect ratio, cells will span two columns; As said previously, most of the rendering involves reading values backward to match the text mode coordinates system. The following routines use X for the horizontal position and Y for the vertical position:

''
'' Draw grid at X, Y. Rendering is done top to bottom, right (smaller value)
'' to left (bigger value.) The three bottom rows, and columns 0, 1, 2, 13, 14,
'' 15 are not drawn (replaced by # symbol here.)
''
SUB drawGrid (x AS INTEGER, y AS INTEGER)
  DIM i AS INTEGER, j AS INTEGER, s AS STRING * 32

  ' Display offset
  LOCATE y

  ' Go through each row (top to bottom, ignore bottom padding)
  FOR i = 0 TO 19

    ' Test all 16 cells (columns, right to left)
    s = SPACE$(32)
    FOR j = 15 TO 0 STEP -1
      IF (grid(i) AND (2 ^ j)) THEN
        MID$(s, 1 + (15 - j) * 2, 2) = CHR$(219) + CHR$(219)
      END IF
    NEXT j

    ' Draw
    LOCATE , x: PRINT "######"; MID$(s, 7, 20); "######"; i
  NEXT i
  PRINT STRING$(32, "#"); 20
  PRINT STRING$(32, "#"); 21
  PRINT STRING$(32, "#"); 22
END SUB

''
'' Draw pattern P at X, Y. Patterns are rendered bottom to top,
'' and right to left. Each cell takes two columns. Empty cells
'' do not erase screen content.
''
SUB drawPattern (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM tmp AS INTEGER, i AS INTEGER

  ' Copy pattern value
  tmp = p

  ' Process all four rows, starting from the bottom
  FOR i = 3 TO 0 STEP -1

    ' Test all four cells
    LOCATE y + i
    IF (tmp AND &H1) THEN LOCATE , x + 6: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H2) THEN LOCATE , x + 4: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H4) THEN LOCATE , x + 2: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H8) THEN LOCATE , x: PRINT CHR$(219); CHR$(219);

    ' Shift bits right, crop lowest row
    tmp = SHR%(tmp, 4)
  NEXT i
END SUB

The game code

The following listing covers the basics and leaves a lot of room for improvement (player score, show next piece, sound, controlled randomness, improved graphics, better controls...) Be creative and have fun!

DECLARE SUB drawGrid (x AS INTEGER, y AS INTEGER)
DECLARE SUB drawPattern (x AS INTEGER, y AS INTEGER, p AS INTEGER)
DECLARE SUB blockMerge (x AS INTEGER, y AS INTEGER, p AS INTEGER)
DECLARE SUB clearRow ()
DECLARE FUNCTION moveValid% (x AS INTEGER, y AS INTEGER, p AS INTEGER)

DECLARE FUNCTION SHR% (i AS INTEGER, b AS INTEGER)
DECLARE FUNCTION SHL% (i AS INTEGER, b AS INTEGER)

CONST flgUpdateGrid = &H1             ' Request: refresh game board
CONST flgMoveDown = &H2               ' Request: move pice down

DIM SHARED grid(0 TO 22) AS INTEGER   ' Game board, 23 rows
DIM pattern(0 TO 27) AS INTEGER       ' Patterns (rotated blocks)

DIM plBlk AS INTEGER                  ' Player block index, 0 to 6
DIM plRot AS INTEGER                  ' Player block orientation, 0 to 3
DIM plPat AS INTEGER                  ' Actual pattern code
DIM plX AS INTEGER, plY AS INTEGER    ' Player block coordinates
DIM plKey AS STRING, plInp AS INTEGER ' Player keyboard input string, scancode

DIM flags AS INTEGER                  ' Generic program flags
DIM nextPush AS SINGLE                ' Next push timer


'' Setup patterns ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''

' Decode DATA statements
FOR i% = 0 TO 27
  READ s$
  pattern(i%) = VAL("&h" + s$)
NEXT i%


'' Setup grid ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''

' Place 6 padding columns (3 on either side) and 3 padding rows.
FOR i = 0 TO 19
  grid(i) = &HE007
NEXT i
grid(20) = &HFFFF
grid(21) = &HFFFF
grid(22) = &HFFFF


'' Initial block, clear screen, request grid draw ''''''''''''''''''''''''''''

' Initialize randomizer
RANDOMIZE TIMER

' Give block
plBlk = INT(RND * 7)
plPat = pattern(plBlk * 4)
plX = 9: plY = 3

' Clear screen, request grid draw
CLS
flags = flgUpdateGrid
nextPush = timer + 1.0


'' Main loop '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''

DO

  '' TIMED PUSH DOWN REQUEST ''

  IF (nextPush < timer) then
    nextPush = timer + 1.0
    flags = flags OR flgMoveDown
  END IF


  '' PLAYER INPUT ''

  ' Get scancode
  plKey = INKEY$
  IF (LEN(plKey) = 1) THEN
    plInp = ASC(plKey)
  ELSEIF (LEN(plKey) = 2) THEN
    plInp = CVI(plKey)
  ELSE
    plInp = 0
  END IF

  ' Process scancode
  SELECT CASE plInp
  CASE 27     ' escape (exit)
    EXIT DO

  CASE &H4B00 ' left arrow (move left)
    IF (moveValid%(plX - 1, plY, plPat)) THEN
      plX = plX - 1
      flags = flags OR flgUpdateGrid
    END IF

  CASE &H4D00 ' right arrow (move right)
    IF (moveValid%(plX + 1, plY, plPat)) THEN
      plX = plX + 1
      flags = flags OR flgUpdateGrid
    END IF

  CASE &H4800 ' up arrow (rotate)
    tmpRot% = (plRot + 1) AND &H3
    tmpPat% = pattern((plBlk * 4) + tmpRot%)
    IF (moveValid%(plX, plY, tmpPat%)) THEN
      plRot = tmpRot%
      plPat = tmpPat%
      flags = flags OR flgUpdateGrid
    END IF

  CASE &H5000 ' down arrow (move down)
    flags = flags OR flgMoveDown
    nextPush = timer + 1.0
  END SELECT


  '' PUSH PIECE DOWN ''

  IF (flags AND flgMoveDown) THEN

    ' Move is valid
    IF (moveValid%(plX, plY + 1, plPat)) THEN
      plY = plY + 1

    ' Cannot move down, merge
    ELSE
      blockMerge plX, plY, plPat
      clearRow

      ' Give another block
      plBlk = INT(RND * 7)                  ' Pick block at random
      plPat = pattern(plBlk * 4)            ' Catch pattern code

      ' Reset position and rotation
      plX = 9: plY = 3: plRot = 0

      ' Reset input queue
      DEF SEG = &h40
      POKE &h1A, PEEK(&h1C)
      DEF SEG

      ' If the block is stuck, game over
      IF (moveValid%(plX, plY, plPat) = 0) THEN
        EXIT DO
      END IF
    END IF
    flags = (flags OR flgUpdateGrid) XOR flgMoveDown
  END IF


  '' RENDER ''

  ' Redraw game board
  IF (flags AND flgUpdateGrid) THEN

    ' Draw grid
    drawGrid 1, 1

    ' Draw block
    COLOR 15
    drawPattern 1 + ((plX - 3) * 2), 1 + (plY - 3), plPat
    COLOR 7

    ' Toggle flag off
    flags = flags XOR flgUpdateGrid
  END IF
LOOP

' 7 blocks x 4 orientations = 28 patterns (hexadecimal)
DATA 0660,0660,0660,0660
DATA 2222,0F00,2222,0F00
DATA 0360,4620,0360,4620
DATA 0630,2640,0630,2640
DATA 4460,0740,0622,02E0
DATA 2260,0470,0644,0E20
DATA 0270,0464,0E40,2620

''
'' Merge pattern P in game board at X, Y.
''
SUB blockMerge (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM x2 AS INTEGER

  ' Invert horizontal axis
  x2 = 15 - x

  ' Place piece
  grid(y - 3) = grid(y - 3) OR SHL%((SHR%(p, 12) AND &HF), x2)
  grid(y - 2) = grid(y - 2) OR SHL%((SHR%(p, 8) AND &HF), x2)
  grid(y - 1) = grid(y - 1) OR SHL%((SHR%(p, 4) AND &HF), x2)
  grid(y) = grid(y) OR SHL%(p AND &HF, x2)
END SUB

''
'' Clear rows
''
SUB clearRow
  DIM count AS INTEGER, i AS INTEGER, j AS INTEGER

  ' Count completed lines (ignore bottom padding)
  FOR i = 19 TO 0 STEP -1
    count = count - (grid(i) = &HFFFF)
  NEXT i

  ' No row completed
  IF (count = 0) THEN EXIT SUB

  ' Search for complete rows
  FOR i = 19 TO 1 STEP -1
    ' This row is complete
    IF (grid(i) = &HFFFF) THEN
      ' Search for next potential incomplete row
      FOR j = i - 1 TO 0 STEP -1
        ' This row is incomplete
        IF (grid(j) <> &HFFFF) THEN
          ' Make complete row swallow incomplete row
          grid(i) = grid(j)
          grid(j) = &HFFFF
          EXIT FOR
        END IF
      NEXT j
    END IF
  NEXT i

  ' Clear top rows (restore left and right padding columns)
  FOR i = 0 TO count - 1
    grid(i) = &HE007
  NEXT i
END SUB

''
'' Draw grid at X, Y. Rendering is done top to bottom, right (smaller value)
'' to left (bigger value.) Ideally the three bottom rows, and columns 0, 1, 2,
'' 13, 14, 15 shouldn't be drawn.
''
SUB drawGrid (x AS INTEGER, y AS INTEGER)
  DIM i AS INTEGER, j AS INTEGER, s AS STRING * 32

  ' Display offset
  LOCATE y

  ' Go through each row (top to bottom, ignore bottom padding)
  FOR i = 0 TO 19

    ' Test all 16 cells (columns, right to left)
    s = SPACE$(32)
    FOR j = 15 TO 0 STEP -1
      IF (grid(i) AND (2 ^ j)) THEN
        MID$(s, 1 + (15 - j) * 2, 2) = CHR$(219) + CHR$(219)
      END IF
    NEXT j

    ' Draw
    LOCATE , x: PRINT "######"; MID$(s, 7, 20); "######"; i
  NEXT i
  PRINT STRING$(32, "#"); 20
  PRINT STRING$(32, "#"); 21
  PRINT STRING$(32, "#"); 22
END SUB

''
'' Draw pattern P at X, Y. Patterns are rendered bottom to top,
'' and right to left. Each cell takes two columns. Empty cells
'' do not erase screen content.
''
SUB drawPattern (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM tmp AS INTEGER, i AS INTEGER

  ' Copy pattern value
  tmp = p

  ' Process all four rows, starting from the bottom
  FOR i = 3 TO 0 STEP -1

    ' Test all four cells
    LOCATE y + i
    IF (tmp AND &H1) THEN LOCATE , x + 6: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H2) THEN LOCATE , x + 4: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H4) THEN LOCATE , x + 2: PRINT CHR$(219); CHR$(219);
    IF (tmp AND &H8) THEN LOCATE , x: PRINT CHR$(219); CHR$(219);

    ' Shift bits right, crop lowest row
    tmp = SHR%(tmp, 4)
  NEXT i
END SUB

''
'' Returns true if pattern P located at X, Y is not colliding
'' with the game board.
''
FUNCTION moveValid% (x AS INTEGER, y AS INTEGER, p AS INTEGER)
  DIM w AS INTEGER, x2 AS INTEGER

  ' Invert horizontal axis
  x2 = 15 - x

  ' Get 4x4 window
  w = ((SHL%((SHR%(grid(y - 3), x2) AND &HF), 12)) OR _
      (SHL%((SHR%(grid(y - 2), x2) AND &HF), 8)) OR _
      (SHL%((SHR%(grid(y - 1), x2) AND &HF), 4)) OR _
      ((SHR%(grid(y), x2) AND &HF)))

  ' Return collision status
  moveValid% = ((w AND p) = 0)
END FUNCTION

''
'' Shift Bits Left
''
FUNCTION SHL% (i AS INTEGER, b AS INTEGER)
  DIM s AS INTEGER

  SELECT CASE b
  CASE IS < 1
    SHL% = i
  CASE IS > 15
    SHL% = 0
  CASE ELSE
    s = (2 ^ (15 - b))
    IF (i AND s) THEN
      SHL% = (i AND (s - 1)) * (2 ^ b) OR &H8000
    ELSE
      SHL% = (i AND (s - 1)) * (2 ^ b)
    END IF
  END SELECT
END FUNCTION

''
'' Shift Bits Right
''
FUNCTION SHR% (i AS INTEGER, b AS INTEGER)
  SELECT CASE b
  CASE IS < 1
    SHR% = i
  CASE IS > 15
    SHR% = 0
  CASE ELSE
    IF (i AND &H8000) THEN
      SHR% = ((i XOR &H8000) \ (2 ^ b)) OR (2 ^ (15 - b))
    ELSE
      SHR% = i \ (2 ^ b)
    END IF
  END SELECT
END FUNCTION

- Mike Hawk