Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
vs (Very Simple) GUI
#1
Trying out an array of Buttons with vs GUI.

I finally got around to fixing the AI to make it unbeatable in Tic Tac Toe. Hear that ARB? UNBEATABLE ;-))

Here is a screen shot:
   

Simply 9 buttons on the screen with message box comments thrown in as needed so as to not spoil the board setup.

In the snap you see the listing of the zip file which includes the fixed Tic Tac Toe with AI code I updated today before converting it to GUI.
Here is what the code looks like for GUI (without the BI/BM).
Code: (Select All)
Option _Explicit
' _Title "GUI Tic Tac Toe with AI"  ' b+ 2022-07-12 try GUI version with fixed AI and a Btn Array!
'      Needs fixing   https://www.youtube.com/watch?v=5n2aQ3UQu9Y
' you start at corner
' they AI play middle to at least tie
' you play opposite corner
' they or AI plays corner will loose!!! I am saying in AI always play corner is not always right!!!
' they have to play side to just tie
'
' 2022-07-12 finally got around to fixing this program
' 2022-07-12 Now try it out with vsGUI, can I use an array of control handles? Yes.

'$include:'vs GUI.BI'

'   Set Globals from BI              your Title here VVV
Xmax = 502: Ymax = 502: GuiTitle$ = "GUI Tic-Tac-Toe with AI"
OpenWindow Xmax, Ymax, GuiTitle$, "ARLRDBD.TTF"

Dim Shared As Long Btn(0 To 8) ' our 9 buttons for the game
Dim As Long x, y, i
For y = 0 To 2 '        yes in, vs GUI, we Can have arrays of controls!!!
    For x = 0 To 2
        Btn(i) = NewControl(1, x * 175 + 1, y * 175 + 1, 150, 150, 120, 600, 668, "")
        i = i + 1
    Next
Next ' that's all for the GUI

' one time sets
Dim Shared Player$, AI$, Turn$, Winner$
Dim Shared As Long PlayerStarts, Count, Done
Dim Shared board$(2, 2) 'store X and O here 3x3
Player$ = "X": AI$ = "O": PlayerStarts = 0

ResetGame
MainRouter

Sub ResetGame
    Dim As Long i, rc, bx, by
    Winner$ = "": Count = 0: Done = 0: Erase board$ 'reset
    For i = 0 To 8
        con(Btn(i)).Text = ""
        drwBtn i + 1, 0
    Next
    PlayerStarts = 1 - PlayerStarts
    If PlayerStarts Then Turn$ = Player$ Else Turn$ = AI$
    If Turn$ = AI$ Then
        rc = AIchoice
        con(rc + 1).Text = AI$
        bx = rc Mod 3: by = Int(rc / 3)
        board$(bx, by) = AI$
        _Delay 3 'let player think AI is thinking
        drwBtn rc + 1, 0
        Count = Count + 1
        'If checkwin Then Winner$ = AI$
        Turn$ = Player$
        mBox "The AI has started the next game.", "It's your turn."
        'now wait for MainRouter to detect a Button click
    End If
End Sub

Function checkwin
    Dim As Long i
    For i = 0 To 2
        If (board$(0, i) = board$(1, i) And board$(1, i) = board$(2, i)) And (board$(2, i) <> "") Then checkwin = 1: Exit Function
    Next
    For i = 0 To 2
        If (board$(i, 0) = board$(i, 1) And board$(i, 1) = board$(i, 2)) And board$(i, 2) <> "" Then checkwin = 1: Exit Function
    Next
    If (board$(0, 0) = board$(1, 1) And board$(1, 1) = board$(2, 2)) And board$(2, 2) <> "" Then checkwin = 1: Exit Function
    If (board$(0, 2) = board$(1, 1) And board$(1, 1) = board$(2, 0)) And board$(2, 0) <> "" Then checkwin = 1
End Function

Function AIchoice
    Dim As Long r, c
    'test all moves to win
    For r = 0 To 2
        For c = 0 To 2
            If board$(c, r) = "" Then
                board$(c, r) = AI$
                If checkwin Then
                    board$(c, r) = ""
                    AIchoice = 3 * r + c
                    Exit Function
                Else
                    board$(c, r) = ""
                End If
            End If
        Next
    Next

    'still here? then no winning moves for AI, how about for player$
    For r = 0 To 2
        For c = 0 To 2
            If board$(c, r) = "" Then
                board$(c, r) = Player$
                If checkwin Then
                    board$(c, r) = ""
                    AIchoice = 3 * r + c 'spoiler move!
                    Exit Function
                Else
                    board$(c, r) = ""
                End If
            End If
        Next
    Next

    'still here? no winning moves, no spoilers then is middle sq available
    If board$(1, 1) = "" Then AIchoice = 4: Exit Function

    ' one time you dont want a corner when 3 moves made human has opposite corners, then defense is any side!
    If (board$(0, 0) = Player$ And board$(2, 2) = Player$) Or (board$(2, 0) = Player$ And board$(0, 2) = Player$) Then
        ' try a side order?
        If board$(1, 0) = "" Then AIchoice = 1: Exit Function
        If board$(0, 1) = "" Then AIchoice = 3: Exit Function
        If board$(2, 1) = "" Then AIchoice = 5: Exit Function
        If board$(1, 2) = "" Then AIchoice = 7: Exit Function

        'still here still? how about a corner office?
        If board$(0, 0) = "" Then AIchoice = 0: Exit Function
        If board$(2, 0) = "" Then AIchoice = 2: Exit Function
        If board$(0, 2) = "" Then AIchoice = 6: Exit Function
        If board$(2, 2) = "" Then AIchoice = 8: Exit Function
    Else
        'still here still? how about a corner office?
        If board$(0, 0) = "" Then AIchoice = 0: Exit Function
        If board$(2, 0) = "" Then AIchoice = 2: Exit Function
        If board$(0, 2) = "" Then AIchoice = 6: Exit Function
        If board$(2, 2) = "" Then AIchoice = 8: Exit Function

        'still here??? a side order then!
        If board$(1, 0) = "" Then AIchoice = 1: Exit Function
        If board$(0, 1) = "" Then AIchoice = 3: Exit Function
        If board$(2, 1) = "" Then AIchoice = 5: Exit Function
        If board$(1, 2) = "" Then AIchoice = 7: Exit Function
    End If
End Function

Sub BtnClickEvent (i As Long) ' Basically the game is played here with player's button clicks
    Dim As Long rc, bx, by
    ' note Btn(0) = 1, Btn(1) = 2...
    rc = i - 1 ' from control number to button number
    bx = rc Mod 3: by = Int(rc / 3) ' from button number to board$ x, y location
    If board$(bx, by) = "" Then ' update board, check win, call AI for it's turn, update board, check win
        con(i).Text = Player$
        drwBtn i, 0
        board$(bx, by) = Player$
        If checkwin Then
            mBox "And the Winner is", "You! Congratulations AI was supposed to be unbeatable."
            ResetGame
        Else
            Count = Count + 1
            If Count >= 9 Then
                mBox "Out of Spaces:", "The Game is a draw."
                ResetGame
            Else ' run the ai
                rc = AIchoice
                con(rc + 1).Text = AI$
                bx = rc Mod 3: by = Int(rc / 3)
                board$(bx, by) = AI$
                _Delay 1 'let player think AI is thinking
                drwBtn rc + 1, 0
                If checkwin Then
                    mBox "And the Winner is", "AI, the AI is supposed to be unbeatable."
                    ResetGame
                Else
                    Count = Count + 1
                    If Count >= 9 Then
                        mBox "Out of Spaces:", "The Game is a draw."
                        ResetGame
                    Else
                        Turn$ = Player$
                    End If
                End If
            End If
        End If
    Else
        Beep: mBox "Player Error:", "That button has already been played."
    End If
End Sub

' this is to keep MainRouter in, vs GUI.BM, happy =========================================
Sub LstSelectEvent (control As Long)
    Select Case control
    End Select
End Sub

Sub PicClickEvent (i As Long, Pmx As Long, Pmy As Long)
    Select Case i
    End Select
End Sub

Sub PicFrameUpdate (i As Long)
    Select Case i
    End Select
End Sub

'$include:'vs GUI.BM'


Attached Files
.zip   vs GUI Tic Tac Toe with AI.zip (Size: 44.42 KB / Downloads: 65)
b = b + ...
Reply
#2
I think that the payer that moves first can always win
Reply
#3
0 1 2
3 4 5
6 7 8

0 is top left, 4 middle, 8 bottom right.

You move first, I bet I tie at least.

I have watched this and have a defense: https://www.youtube.com/watch?v=5n2aQ3UQu9Y
b = b + ...
Reply
#4
Sometime ago I created a Tabulator App that took a Function F(x) = (string), a bunch of variables = values in a chr$(10) delimited string and xStart, xEnd, xInc like a For... Next Loop all these go into a TableIn.txt file that the Tabulator reads and produces a Table of x F(x) Data that could be read in by another bas app that needed the data for a function on the fly ie doesn't have to be formally defined in the app.

Then I made a demo of how to use the Tabulator and that was that, until now I have GUI.

Now I can use GUI to Interface with the Tabulator and Graph Functions. Here are a few I tried tonight:
Simple Quadratic:
   

A trig function:
   

Another:
   

Here is the code for GUI:
Code: (Select All)
Option _Explicit ' _Title "GUI Interface with Tabulator for Plotting F(x)" ' b+ 2022-07-14

'$include:'vs GUI.BI'

'   Set Globals from BI
Xmax = 1280: Ymax = 700: GuiTitle$ = "GUI Interface with Tabulator for Plotting F(x)" ' <<<<<  Window size shared throughout program
OpenWindow Xmax, Ymax, GuiTitle$, "arial.ttf" ' need to do this before drawing anything from NewControls
' name = NewControl(0, 0, 0, 0, 0, 0, 0, 0, "text")
' GUI Controls
'                     Dim and set Globals for GUI app
Dim Shared As Long lbFx, tbFx, lbVV, tbVV, btAdd, lbVLst, lsVV, btEdit, btDelete, btPlot, lbx, tbStart, tbEnd, tbInc, pPlot
lbFx = NewControl(4, 10, 10, 560, 30, 30, 0, 0, "Formula F(x)")
tbFx = NewControl(2, 10, 40, 560, 30, 20, 0, 0, "")
lbVV = NewControl(4, 10, 80, 560, 30, 30, 0, 0, "Variable = Value")
tbVV = NewControl(2, 10, 110, 490, 30, 20, 0, 0, "")
btAdd = NewControl(1, 510, 110, 60, 30, 20, 0, 0, "Add")
lbVLst = NewControl(4, 10, 150, 560, 30, 30, 0, 0, "Variable and Value List:")
lsVV = NewControl(3, 10, 180, 560, 380, 20, 0, 0, "")
btEdit = NewControl(1, 10, 570, 180, 40, 30, 0, 0, "Edit")
btDelete = NewControl(1, 200, 570, 180, 40, 30, 0, 0, "Delete")
btPlot = NewControl(1, 390, 570, 180, 40, 30, 0, 0, "Plot")
lbx = NewControl(4, 10, 620, 550, 30, 20, 0, 0, "X:Start                    X:End                           ")
tbStart = NewControl(2, 10, 650, 180, 40, 20, 0, 0, "")
tbEnd = NewControl(2, 200, 650, 180, 40, 20, 0, 0, "")
'tbInc = NewControl(2, 390, 650, 180, 40, 20, 0, 0, "")
pPlot = NewControl(5, 580, 0, 700, 700, 0, 999, 0, "")
' End GUI Controls

MainRouter ' after all controls setup

'  EDIT these to your programs needs
Sub BtnClickEvent (i As Long) ' attach you button click code in here
    Dim item$
    Select Case i
        Case btAdd
            If _Trim$(con(tbVV).Text) <> "" Then
                If _Trim$(con(lsVV).Text) <> "" Then
                    con(lsVV).Text = con(lsVV).Text + "~" + _Trim$(con(tbVV).Text)
                Else
                    con(lsVV).Text = con(tbVV).Text
                End If
                con(tbVV).Text = ""
                drwTB tbVV, tbVV = ActiveControl
                drwLst lsVV, lsVV = ActiveControl
            End If
        Case btEdit
            ReDim lst(1 To 1) As String
            Split con(lsVV).Text, "~", lst()
            item$ = lst((con(lsVV).N1 - 1) * con(lsVV).N4 + con(lsVV).N2)
            con(tbVV).Text = item$
            drwTB tbVV, tbVV = ActiveControl
            Remove item$, lst()
            con(lsVV).Text = Join$(lst(), "~")
            drwLst lsVV, tbVV = ActiveControl
        Case btDelete ' what is the highlited
            ReDim lst(1 To 1) As String
            Split con(lsVV).Text, "~", lst()
            item$ = lst((con(lsVV).N1 - 1) * con(lsVV).N4 + con(lsVV).N2)
            Remove item$, lst()
            con(lsVV).Text = Join$(lst(), "~")
            drwLst lsVV, 0
        Case btPlot
            ' make call to Tabulator (in Shell)
            ReDim As Long j
            Dim xStart, xEnd, yMin, yMax, dx, y(700), dy, x, y
            Dim fx$
            ReDim lst(0)
            xStart = Val(_Trim$(con(tbStart).Text)): xEnd = Val(_Trim$(con(tbEnd).Text))
            dx = (xEnd - xStart) / 700: fx$ = _Trim$(con(tbFx).Text)
            Split con(lsVV).Text, "~", lst()
            item$ = Join$(lst(), Chr$(10)) ' reusing something already DIM's this is our variable list delimited by chr$(10)
            ReDim arr$(0)
            If dx = 0 Then Cls: Print "dx = 0": End
            forXEqual xStart, xEnd, dx, fx$, 0, item$, arr$() ' 0 = using radians for trig
            ' hopefully arr$ has the data we need to make our plot

            'debug
            'item$ = Join$(arr$(), Chr$(10)) ' debug
            'mBox "Our Data Array", item$ ' debug   with 700 items in table probably don't want to check in mbox

            ' need to find min, max y and convert values to number
            For j = 0 To 700
                y(j) = Val(_Trim$(RightOf$(arr$(j), " ")))
                If j = 0 Then
                    yMax = y(j): yMin = y(j)
                Else
                    If y(j) < yMin Then
                        yMin = y(j)
                    ElseIf y(j) > yMax Then
                        yMax = y(j)
                    End If
                End If
            Next j
            yMin = yMin - 10
            yMax = yMax + 10
            dy = yMax - yMin
            If dy <> 0 Then ' dont divide by 0
                _Dest con(pPlot).N1
                Line (0, 0)-Step(con(pPlot).W - 1, con(pPlot).H - 1), &HFFEEEEFF, BF

                If 0 >= xStart And 0 <= xEnd Then
                    Line (700 * (0 - xStart) / (xEnd - xStart), 0)-Step(0, 700), Black ' y axis
                    For y = -10 To 10
                        Line (700 * (-xStart) / (xEnd - xStart) - 3, 700 - 700 * (y - yMin) / (yMax - yMin))-Step(6, 0), Black
                    Next
                End If

                If 0 >= yMin And 0 <= yMax Then
                    Line (0, 700 - 700 * (0 - yMin) / (yMax - yMin))-Step(700, 0), Black ' y axis
                    For x = -10 To 10
                        Line (700 * (x - xStart) / (xEnd - xStart), 700 - 700 * (0 - yMin) / (yMax - yMin) - 3)-Step(0, 6), Black ' y axis
                    Next
                End If
                For j = 0 To 700
                    Circle (j, con(pPlot).H - 1 - 700 * (y(j) - yMin) / dy), 1, &HFF0000FF
                    PSet (j, con(pPlot).H - 1 - 700 * (y(j) - yMin) / dy), &HFF0000FF
                Next
                _Dest 0
                _PutImage (con(pPlot).X, con(pPlot).Y)-Step(con(pPlot).W, con(pPlot).H), con(pPlot).N1, 0
            End If

    End Select
End Sub

Sub LstSelectEvent (control As Long)
    Select Case control
    End Select
End Sub

Sub PicClickEvent (i As Long, Pmx As Long, Pmy As Long) ' attach your Picture click code in here
    Select Case i
    End Select
End Sub

Sub PicFrameUpdate (i As Long) ' attach your Picture click code in here
    Select Case i
    End Select
End Sub

Sub forXEqual (start, toFinish, incStep, formula$, dFlag As Long, variablesCHR10$, outputArr$())
    Dim fLine$
    If _FileExists("TableOut.txt") Then Kill "TableOut.txt"
    Open "TableIn.txt" For Output As #1
    Print #1, _Trim$(Str$(start))
    Print #1, _Trim$(Str$(toFinish))
    Print #1, _Trim$(Str$(incStep))
    Print #1, formula$
    Print #1, TS$(dFlag)
    Print #1, variablesCHR10$
    Close #1
    ReDim outputArr$(0)
    Shell _Hide "Tabulator.exe"
    _Delay .5 ' sometimes it compiles in time sometimes not, 3 reduces the nots
    If _FileExists("TableOut.txt") Then
        Open "TableOut.txt" For Input As #1
        While Not EOF(1)
            Line Input #1, fLine$
            sAppend outputArr$(), fLine$
        Wend
        Close #1
    End If
End Sub

''append to the string array the string item
Sub sAppend (arr() As String, addItem$)
    ReDim _Preserve arr(LBound(arr) To UBound(arr) + 1) As String
    arr(UBound(arr)) = addItem$
End Sub

'$include:'vs GUI.BM'

And here is the zip with the Tabulator.exe for Windows so can run GUI right out of package if on Windows, otherwise compile for your OS before running GUI Interface. Again the Tabulator works with 2 simple files TableIn.txt and TableOut.txt. Included also is the Tabulator Demo for using in bas code.

Update 2022-07-17: I am updating the zip file with an improved plotting, drawing a line from last x to next, this radically changes the 3rd graph shown above without effecting the other 2.


Attached Files
.zip   GUI Interface with Tabulator For Plotting.zip (Size: 2.31 MB / Downloads: 60)
b = b + ...
Reply
#5
BTW I have found things to be much simpler by assuming the highlighted item in a List Box IS the selected item when working with an associated Button for a selected item out of the list. That is how the Edit and Delete buttons are working for the above GUI Interface.

I kinda like the default colors for vs GUI, reminds me of a favorite PL IDE.
b = b + ...
Reply
#6
I'm trying your Tic-Tac-Toe game but I can't get your libraries to be found for some reason. I've tried moving files around, etc. but no luck. Is there a certain folder they need to go in now? I've used them before but I just had to keep them in the same directory.
Reply
#7
Everything you need is in that zip folder.

OK you've downloaded the zip,
Extracted the files as a folder all together.
Have QB64 IDE Run Menu set Output exe to Source Folder ( a little bullet on the left).
Loaded the GUI TTT with AI.bas file into the IDE
Run the file and the TTT Board should come up.

Everything is self contained in the folder. Don't move the files around, they all have to be together in the one folder, the BI, BM with the bas and the exe ends up there too.
b = b + ...
Reply
#8
@ARB the program is an exe file only, no source .bas file, correct?
b = b + ...
Reply
#9
Quote:Do you mean your AI has finally caught up with mine! ?  Smile  Well sorry to say your a year behind my Perfect playing program attached Big Grin ...
yeah well... different priorities I guess ;-))


Quote:
bplus Wrote: Wrote:@ARB the program is an exe file only, no source .bas file, correct?

Yes! ? Just run the program in one Window and your program in another and play them against each other move by move,if your Paranoid about my program being able to read what your program is thinking ? then run them on different Computers,or even off an external USB Linux live distro running Wine.


No I am not paranoid about your exe's, it's just that the bas is what is interesting to me. I like to see how you get it to do what it does.

Otherwise, I might as well download a random TTT program off Internet to play TTT, it's boring playing a black box!

We are a programming forum honing and showing off our QB64 coding skills; game sharing and playing is for other places.

For instance, this is the code I added for AI to defend against the human should they start at one corner (AI picks middle) and human picks the corner opposite the first corner. A guaranteed win for human IF AI played a corner so the fix was this addition:
Code: (Select All)
    ' one time you dont want a corner when 3 moves made human has opposite corners, then defense is any side!
    If (board$(0, 0) = Player$ And board$(2, 2) = Player$) Or (board$(2, 0) = Player$ And board$(0, 2) = Player$) Then
        ' try a side order?
        If board$(1, 0) = "" Then AIchoice = 1: Exit Function
        If board$(0, 1) = "" Then AIchoice = 3: Exit Function
        If board$(2, 1) = "" Then AIchoice = 5: Exit Function
        If board$(1, 2) = "" Then AIchoice = 7: Exit Function

        'still here still? how about a corner office?
        If board$(0, 0) = "" Then AIchoice = 0: Exit Function
        If board$(2, 0) = "" Then AIchoice = 2: Exit Function
        If board$(0, 2) = "" Then AIchoice = 6: Exit Function
        If board$(2, 2) = "" Then AIchoice = 8: Exit Function
    Else

Now that is something useful a QB64 coder might use for their TTT perfect playing AI.
b = b + ...
Reply
#10
I might have found the problem, it probably has to do with the fact that I keep all my QB64 apps in a completely different directory than QB64. I started doing that recently so I wouldn't lose them when I update QB64. But I just opened the .BI file inside QB64 and the error was that it couldn't locate direntry.h I tried to put that in the same directory as your game but no luck. Then I tried putting it outside of the directory but still no luck. I also tried putting it in its own directory in both locations and no luck. But the strange thing is, I also tried your game inside my QB64 folder and it still wouldn't find it. I might be using the wrong direntry.h file or just don't have the right one. Your BI file says to look at your GUI.txt file but that wasn't included in your zip so I don't have it.
Reply




Users browsing this thread: 1 Guest(s)