Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
You're a bandit!
#1
Smile 
This is a funny game that is modelled after one found in a book called "Apple Pascal Games" that I borrowed from the library a long time ago. Sorry don't remember who were the authors of that book...

The book had a bunch of text-mode games. The original game was a bit lame taking something from the famous "Robotwar" causing the computer-controlled enemy to move toward the player always. The program presented here is a lot like the original from the book but has five levels. There is another difference: like "Robotwar", the playing board is surrounded by a fence. If the "bandit" runs into it the game is over.

The keys to move the player kind of suck but my laptop doesn't have a numeric keypad. They are [7][8][9] for the top, [U] and [O] for left and right, and [J][K][L] for the bottom. I changed it for this post, so the number keys except 0 and 5 could be used to move no matter where those keys are found. On the number pad of your keyboard, of course make sure Numlock is enabled. This program could be a lot more fun with a joystick and/or with two enemies instead of one. Press [ESC] to quit the program.

Code: (Select All)
'by mnrvovrfc 23-Mar-2023
OPTION _EXPLICIT

DIM AS INTEGER top, lef, bot, rig, lvl, chc, i, j, wid
DIM AS INTEGER px, py, bx, by, cx, cy, ox, oy, score
DIM AS _BYTE quit, die, goon, permission, finis
DIM a$, t$, treasure$, namlvl$(1 TO 5)
treasure$ = "@$" + CHR$(244) + CHR$(176) + CHR$(4)
namlvl$(1) = "honey bun"
namlvl$(2) = "lotta money"
namlvl$(3) = "candy cane"
namlvl$(4) = "graham cracker"
namlvl$(5) = "diamond"
top = 1: lef = 1
bot = 22: rig = 80
lvl = 1

_TITLE "You're a BANDIT!"
DO
    COLOR 15, 0: CLS
    wid = rig - lef + 1
    a$ = STRING$(wid, 35)
    LOCATE top, lef: PRINT a$;
    LOCATE bot, lef: PRINT a$;
    FOR j = top + 1 TO bot - 1
        LOCATE j, lef: PRINT "#";
        LOCATE j, rig: PRINT "#";
    NEXT

    px = Rand(lef + 1, 39)
    py = Rand(top + 1, 11)
    bx = Rand(40, rig - 1)
    by = Rand(12, bot - 1)
    cx = Rand(40, rig - 1)
    cy = Rand(top + 1, 11)

    t$ = MID$(treasure$, lvl, 1)
    LOCATE py, px: PRINT "R";
    LOCATE by, bx: PRINT t$;
    LOCATE cy, cx: PRINT CHR$(206);
    DO
        _LIMIT 100
        j = 0
        FOR i = 49 TO 117
            SELECT CASE i
                CASE 49, 50, 51, 52, 54, 55, 56, 57, 106, 107, 108, 111, 117
                    IF _KEYDOWN(i) THEN j = j + 1
            END SELECT
        NEXT
    LOOP UNTIL j = 0
    LOCATE 23, 1: PRINT "Go get that "; namlvl$(lvl); "!"

    chc = 10
    quit = 0
    die = 0
    DO
        _LIMIT 14
        ox = -1: oy = -1
        permission = 0
        IF _KEYDOWN(27) THEN quit = 1
        IF _KEYDOWN(55) THEN
            ox = px: oy = py
            px = px - 1: py = py - 1
        ELSEIF _KEYDOWN(56) THEN
            ox = px: oy = py
            py = py - 1
        ELSEIF _KEYDOWN(57) THEN
            ox = px: oy = py
            px = px + 1: py = py - 1
        ELSEIF _KEYDOWN(49) OR _KEYDOWN(106) THEN
            ox = px: oy = py
            px = px - 1: py = py + 1
        ELSEIF _KEYDOWN(50) OR _KEYDOWN(107) THEN
            ox = px: oy = py
            py = py + 1
        ELSEIF _KEYDOWN(51) OR _KEYDOWN(108) THEN
            ox = px: oy = py
            px = px + 1: py = py + 1
        ELSEIF _KEYDOWN(52) OR _KEYDOWN(117) THEN
            ox = px: oy = py
            px = px - 1
        ELSEIF _KEYDOWN(54) OR _KEYDOWN(111) THEN
            ox = px: oy = py
            px = px + 1
        END IF
        DO
            IF ox <> -1 AND oy <> -1 THEN
                IF SCREEN(py, px) = 35 THEN
                    LOCATE oy, ox: PRINT " ";
                    LOCATE by, bx: PRINT t$;
                    LOCATE py, px: PRINT CHR$(15);
                    die = 2
                    EXIT DO
                END IF
                permission = 1
                LOCATE oy, ox: PRINT " ";
                LOCATE by, bx: PRINT t$;
                LOCATE py, px: PRINT "R";
                IF px = cx AND py = cy THEN die = 1
                IF px = bx AND py = by THEN
                    score = score + 1
                    LOCATE 24, 1: PRINT "Score ="; score; "| Level ="; lvl;
                    chc = chc - 1
                    IF chc < 1 THEN finis = 1
                    bx = Rand(lef, 39)
                    by = Rand(top, 11)
                    IF px < 40 THEN bx = Rand(40, rig - 1) ELSE bx = Rand(lef + 1, 39)
                    IF py < 12 THEN by = Rand(12, bot - 1) ELSE by = Rand(top + 1, 11)
                END IF
            END IF
        LOOP UNTIL 1
        IF die OR finis THEN EXIT DO
        IF permission THEN
            'goon = (chc = 1)
            'IF goon = 0 THEN goon = (INT(RND * chc + 1) = 1)
            goon = (RND * chc + 1.25 < 2)
            IF goon THEN
                ox = cx: oy = cy
                IF px < cx THEN cx = cx - 1 ELSE IF px > cx THEN cx = cx + 1
                IF py < cy THEN cy = cy - 1 ELSE IF py > cy THEN cy = cy + 1
                LOCATE oy, ox: PRINT " ";
                LOCATE by, bx: PRINT t$;
                LOCATE cy, cx: PRINT CHR$(206);
                IF px = cx AND py = cy THEN die = 1
            END IF
        END IF
    LOOP UNTIL quit OR die OR finis

    LOCATE 23, 1: PRINT SPACE$(79);
    IF die THEN
        PLAY "T200L8"
        LOCATE 23, 1
        IF die = 1 THEN
            PRINT "The bandit has been caught!";
            FOR j = 8 TO 80 STEP 5
                PLAY "N" + _TRIM$(STR$(j))
            NEXT
        ELSEIF die = 2 THEN
            PRINT "Cheater! Stop trying to run out of bounds LOL.";
            FOR j = 5 TO 11000 STEP 384
                i = INT(SIN(_D2R(j)) * ABS(30 - 40 * (j > 2000)) + 6)
                IF i < 6 THEN i = 6
                IF i > 80 THEN i = 80
                PLAY "N" + _TRIM$(STR$(i))
            NEXT
        END IF
    ELSEIF finis THEN
        lvl = lvl + 1
        IF lvl > 5 THEN
            LOCATE 23, 1: PRINT "Guess what? You have beaten the game!";
            PLAY "T200L8"
            FOR j = 10 TO 80 STEP 10
                i = ((j ^ 2.5) MOD 70) + 6
                PLAY "N" + _TRIM$(STR$(i))
                PLAY "N" + _TRIM$(STR$(j))
            NEXT
            quit = 1
        ELSE
            top = top + 1
            bot = bot - 1
            SELECT CASE lvl
                CASE 2
                    lef = lef + 5
                    rig = rig - 5
                CASE 3
                    lef = lef + 9
                    rig = rig - 9
                CASE 4
                    lef = lef + 6
                    rig = rig - 6
                CASE 5
                    lef = lef + 3
                    rig = rig - 3
            END SELECT
            finis = 0
        END IF
    END IF
LOOP UNTIL die OR quit
SYSTEM

FUNCTION Rand& (fromval&, toval&)
    DIM f&, t&, sg%
    IF fromval& = toval& THEN
        Rand& = fromval&
        EXIT FUNCTION
    END IF
    f& = fromval&
    t& = toval&
    IF (f& < 0) AND (t& < 0) THEN
        sg% = -1
        f& = f& * -1
        t& = t& * -1
    ELSE
        sg% = 1
    END IF
    IF f& > t& THEN SWAP f&, t&
    Rand& = INT(RND * (t& - f& + 1) + f&) * sg%
END FUNCTION
Reply
#2
program plays itself
where character is striving for a target
and character avoids enemy
and yet enemy wins

used idea of my program XONIX

https://qb64phoenix.com/forum/showthread.php?tid=519

beginning of program added name bandit.bas
and copying it is easy to save using a ready-made name

Code: (Select All)
'by mnrvovrfc 23-Mar-2023 ' bandit.bas
Option _Explicit: Randomize Timer

Dim As Integer top, lef, bot, rig, lvl, chc, i, j, wid
Dim As Integer px, py, bx, by, cx, cy, ox, oy, score
Dim As _Byte quit, die, goon, permission, finis
Dim a$, t$, treasure$, namlvl$(1 To 5)
treasure$ = "@$" + Chr$(244) + Chr$(176) + Chr$(4)
namlvl$(1) = "honey bun"
namlvl$(2) = "lotta money"
namlvl$(3) = "candy cane"
namlvl$(4) = "graham cracker"
namlvl$(5) = "diamond"
top = 1: lef = 1
bot = 22: rig = 80
lvl = 1

_Title "You're a BANDIT!"
Do
    Color 15, 0: Cls
    wid = rig - lef + 1
    a$ = String$(wid, 35)
    Locate top, lef: Print a$;
    Locate bot, lef: Print a$;
    For j = top + 1 To bot - 1
        Locate j, lef: Print "#";
        Locate j, rig: Print "#";
    Next

    px = Rand(lef + 1, 39)
    py = Rand(top + 1, 11)
    bx = Rand(40, rig - 1)
    by = Rand(12, bot - 1)
    cx = Rand(40, rig - 1)
    cy = Rand(top + 1, 11)

    t$ = Mid$(treasure$, lvl, 1)
    Locate py, px: Print "R";
    Locate by, bx: Print t$;
    Locate cy, cx: Print Chr$(206);
    Do
        _Limit 100
        j = 0
        For i = 49 To 117
            Select Case i
                Case 49, 50, 51, 52, 54, 55, 56, 57, 106, 107, 108, 111, 117
                    If _KeyDown(i) Then j = j + 1
            End Select
        Next
    Loop Until j = 0
    Locate 23, 1: Print "Go get that "; namlvl$(lvl); "!"

    chc = 2
    quit = 0
    die = 0
    Do
        _Limit 14
        ox = 3: oy = 3
        permission = 0
        If _KeyDown(27) Then quit = 1

' Danilin Xonix
        Locate oy, ox: Print " ";
        If py < by Then ox = px: oy = py: py = py + 1
        Locate py, px: Print "R";

        Locate oy, ox: Print " ";
        If py > by Then ox = px: oy = py: py = py - 1
        Locate py, px: Print "R";

        Locate oy, ox: Print " ";
        If px < bx Then ox = px: oy = py: px = px + 1
        Locate py, px: Print "R";

        Locate oy, ox: Print " ";
        If px > bx Then ox = px: oy = py: px = px - 1
        Locate py, px: Print "R";


        Locate oy, ox: Print " ";
        If py = cy Then ox = px: oy = py: py = py + 1
        Locate py, px: Print "R";

        Locate oy, ox: Print " ";
        If px = cx Then ox = px: oy = py: px = px - 1
        Locate py, px: Print "R";
' Danilin Xonix

        Do
            If ox <> -1 And oy <> -1 Then
                If Screen(py, px) = 35 Then

                    Locate by, bx: Print t$;
                    Locate py, px: Print Chr$(15);
                    die = 2
                    Exit Do
                End If
                permission = 1
                Locate oy, ox: Print " ";
                Locate by, bx: Print t$;
                Locate py, px: Print "R";
                If px = cx And py = cy Then die = 1
                If px = bx And py = by Then
                    score = score + 1
                    Locate 24, 1: Print "Score ="; score; "| Level ="; lvl;
                    chc = chc - 1
                    If chc < 1 Then finis = 1
                    bx = Rand(lef, 39)
                    by = Rand(top, 11)
                    If px < 40 Then bx = Rand(40, rig - 1) Else bx = Rand(lef + 1, 39)
                    If py < 12 Then by = Rand(12, bot - 1) Else by = Rand(top + 1, 11)
                End If
            End If
        Loop Until 1
        If die Or finis Then Exit Do
        If permission Then
            'goon = (chc = 1)
            'IF goon = 0 THEN goon = (INT(RND * chc + 1) = 1)
            goon = (Rnd * chc + 1.25 < 2)
            If goon Then
                ox = cx: oy = cy
                If px < cx Then cx = cx - 1 Else If px > cx Then cx = cx + 1
                If py < cy Then cy = cy - 1 Else If py > cy Then cy = cy + 1
                Locate oy, ox: Print " ";
                Locate by, bx: Print t$;
                Locate cy, cx: Print Chr$(206);
                If px = cx And py = cy Then die = 1
            End If
        End If
    Loop Until quit Or die Or finis

    Locate 23, 1: Print Space$(79);
    If die Then
        Play "T200L8"
        Locate 23, 1
        If die = 1 Then
            Print "The bandit has been caught!";
            For j = 8 To 80 Step 5
                Play "N" + _Trim$(Str$(j))
            Next
        ElseIf die = 2 Then
            Print "Cheater! Stop trying to run out of bounds LOL.";
            For j = 5 To 11000 Step 384
                i = Int(Sin(_D2R(j)) * Abs(30 - 40 * (j > 2000)) + 6)
                If i < 6 Then i = 6
                If i > 80 Then i = 80
                Play "N" + _Trim$(Str$(i))
            Next
        End If
    ElseIf finis Then
        lvl = lvl + 1
        If lvl > 5 Then
            Locate 23, 1: Print "Guess what? You have beaten the game!";
            Play "T200L8"
            For j = 10 To 80 Step 10
                i = ((j ^ 2.5) Mod 70) + 6
                Play "N" + _Trim$(Str$(i))
                Play "N" + _Trim$(Str$(j))
            Next
            quit = 1
        Else
            top = top + 1
            bot = bot - 1
            Select Case lvl
                Case 2
                    lef = lef + 5
                    rig = rig - 5
                Case 3
                    lef = lef + 9
                    rig = rig - 9
                Case 4
                    lef = lef + 6
                    rig = rig - 6
                Case 5
                    lef = lef + 3
                    rig = rig - 3
            End Select
            finis = 0
        End If
    End If
Loop Until die Or quit
System

Function Rand& (fromval&, toval&)
    Dim f&, t&, sg%
    If fromval& = toval& Then
        Rand& = fromval&
        Exit Function
    End If
    f& = fromval&
    t& = toval&
    If (f& < 0) And (t& < 0) Then
        sg% = -1
        f& = f& * -1
        t& = t& * -1
    Else
        sg% = 1
    End If
    If f& > t& Then Swap f&, t&
    Rand& = Int(Rnd * (t& - f& + 1) + f&) * sg%
End Function
Write name of program in 1st line to copy & paste & save filename.bas
Insert program pictures: press print-screen-shot button
Open paint & Paste & Save as PNG
Add picture file to program topic

Russia looks world from future. Big data is peace data.
I never recommend anything & always write only about myself
Reply
#3
This sounds pretty interesting. Any screenshots?
Tread on those who tread on you

Reply
#4
Screenshots would spoil the reason to try the program in the first place.

It is just the player token, the bad guy and the "prize", all three surrounded by a fence like in "Robotwar". LOL at "XONIX" there is nothing rebounding like a ball in this game although I've done too many of those...

Now if only I still had that cheap Nintendo-SuperNES-like controller around or a joystick, because "nobody" likes the keystroke combinations in this program...
Reply
#5
milli animation shows as player bypassing of pursuer
in my automatic neuronet nano quantum algorithm

35 kB gif [Image: chaseqb.gif] [Image: chaseqb.gif]

+ see you topic "Chase and Prize Game"

https://qb64phoenix.com/forum/showthread...8#pid14618
Write name of program in 1st line to copy & paste & save filename.bas
Insert program pictures: press print-screen-shot button
Open paint & Paste & Save as PNG
Add picture file to program topic

Russia looks world from future. Big data is peace data.
I never recommend anything & always write only about myself
Reply
#6
Hi
just fine.
Why do you not code the replay?
Reply
#7
Quote:Now if only I still had that cheap Nintendo-SuperNES-like controller around

Search Amazon for "buffalo controller."  Last I checked, they were very cheap, I use them for everything.
Reply




Users browsing this thread: 3 Guest(s)