5 Letter Hangman - SierraKen - 08-29-2022
After playing the 4 Letter Hangman for awhile, I figured out that it was getting pretty easy. So tonight I decided to make a 5 letter version. I found a list online of 5 letter words, like I did with the 4 letter one at one time. Then I made an app that automatically makes the DATA statements for the list. This one chooses from 711 5-letter words. I also added some sky color. Everything else is the same, just one more letter than the other one. Also, as I did with the 4 letter one, I added the LCASE$ command so you don't have to worry about upper or lower case letters, it converts it all to lower case.
Code: (Select All) '5 Letter Hangman by SierraKen - August 28, 2022.
'The game chooses between 711 5-letter words.
_Title "5 Letter Hangman by Sierraken"
start:
Cls
Screen _NewImage(800, 600, 32)
For y = 0 To 400
c = c + .5
Line (0, y)-(800, y), _RGB32(0, 0, c)
Next y
c = 0
Line (0, 400)-(800, 400), _RGB32(255, 255, 255)
Line (600, 400)-(600, 100), _RGB32(255, 255, 255)
Line (600, 100)-(400, 100), _RGB32(255, 255, 255)
Line (400, 100)-(400, 180), _RGB32(255, 255, 255)
For lines = 303 To 503 Step 50
Line (lines, 500)-(lines + 10, 500), _RGB32(255, 255, 255)
Next lines
Randomize Timer
word = Int(Rnd * 711) + 1
For w = 1 To word - 1
Read w$
Next w
Read word$
letter1$ = Mid$(word$, 1, 1)
letter2$ = Mid$(word$, 2, 1)
letter3$ = Mid$(word$, 3, 1)
letter4$ = Mid$(word$, 4, 1)
letter5$ = Mid$(word$, 5, 1)
letter = 0: oldletter = 0: one = 0: two = 0: three = 0: four = 0: five = 0
mistake = 0
go:
Do
_Limit 20
a$ = InKey$
If a$ <> "" Then GoTo continue:
Loop
continue:
a$ = LCase$(a$)
If a$ = Chr$(27) Then End
oldletter = letter
If a$ = letter1$ Then
_PrintString (305, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
one = one + 1
If one = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter2$ Then
_PrintString (355, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
two = two + 1
If two = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter3$ Then
_PrintString (405, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
three = three + 1
If three = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter4$ Then
_PrintString (455, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
four = four + 1
If four = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter5$ Then
_PrintString (505, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
five = five + 1
If five = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If oldletter <> letter Then GoTo go:
mistake = mistake + 1
'Head
If mistake = 1 Then
Circle (400, 200), 20, _RGB32(255, 255, 255)
_PrintString (50, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Body
If mistake = 2 Then
Line (400, 220)-(400, 300), _RGB32(255, 255, 255)
_PrintString (75, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Arm
If mistake = 3 Then
Line (400, 240)-(375, 220), _RGB32(255, 255, 255)
_PrintString (100, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Arm
If mistake = 4 Then
Line (400, 240)-(425, 220), _RGB32(255, 255, 255)
_PrintString (125, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Leg
If mistake = 5 Then
Line (400, 300)-(370, 330), _RGB32(255, 255, 255)
_PrintString (150, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Leg
If mistake = 6 Then
Line (400, 300)-(430, 330), _RGB32(255, 255, 255)
_PrintString (50, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Eyes
If mistake = 7 Then
Circle (390, 190), 3, _RGB32(255, 255, 255)
Circle (410, 190), 3, _RGB32(255, 255, 255)
_PrintString (75, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Nose
If mistake = 8 Then
Circle (400, 200), 3, _RGB32(255, 255, 255)
_PrintString (100, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Mouth
If mistake = 9 Then
Circle (400, 212), 8, _RGB32(255, 255, 255), , , .5
_PrintString (125, 475), a$
For snd = 700 To 100 Step -50
Sound snd, .5
Next snd
_PrintString (305, 480), letter1$
_PrintString (355, 480), letter2$
_PrintString (405, 480), letter3$
_PrintString (455, 480), letter4$
_PrintString (505, 480), letter5$
_PrintString (305, 415), "You Lose!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
Restore
GoTo start:
End If
End
End If
GoTo go:
won:
_PrintString (305, 415), "You Win!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
Restore
GoTo start:
End If
End
Data abuse,adult,agent,anger,apple,award,basis,beach,birth,block,blood
Data blood,board,brain,bread,break,brown,buyer,cause,chain,chair,chest
Data chest,chief,child,china,claim,class,clock,coach,coast,court,cover
Data cover,cream,crime,cross,crowd,crown,cycle,dance,death,depth,doubt
Data doubt,draft,drama,dream,dress,drink,drive,earth,enemy,entry,error
Data error,event,faith,fault,field,fight,final,floor,focus,force,frame
Data frame,frank,front,fruit,glass,grant,grass,green,group,guide,heart
Data heart,henry,horse,hotel,house,image,index,input,issue,japan,jones
Data jones,judge,knife,laura,layer,level,lewis,light,limit,lunch,major
Data major,march,match,metal,model,money,month,motor,mouth,music,night
Data night,noise,north,novel,nurse,offer,order,other,owner,panel,paper
Data paper,party,peace,peter,phase,phone,piece,pilot,pitch,place,plane
Data plane,plant,plate,point,pound,power,press,price,pride,prize,proof
Data proof,queen,radio,range,ratio,reply,right,river,round,route,rugby
Data rugby,scale,scene,scope,score,sense,shape,share,sheep,sheet,shift
Data shift,shirt,shock,sight,simon,skill,sleep,smile,smith,smoke,sound
Data sound,south,space,speed,spite,sport,squad,staff,stage,start,state
Data state,steam,steel,stock,stone,store,study,stuff,style,sugar,table
Data table,taste,terry,theme,thing,title,total,touch,tower,track,trade
Data trade,train,trend,trial,trust,truth,uncle,union,unity,value,video
Data video,visit,voice,waste,watch,water,while,white,whole,woman,world
Data world,youth,there,where,which,whose,whoso,yours,yours,admit
Data admit,adopt,agree,allow,alter,apply,argue,arise,avoid,begin,blame
Data blame,break,bring,build,burst,carry,catch,cause,check,claim,clean
Data clean,clear,climb,close,count,cover,cross,dance,doubt,drink,drive
Data drive,enjoy,enter,exist,fight,focus,force,guess,imply,issue,judge
Data judge,laugh,learn,leave,limit,marry,match,occur,offer,order
Data order,phone,place,point,press,prove,raise,reach,refer,relax,serve
Data serve,shall,share,shift,shoot,sleep,solve,sound,speak,spend,split
Data split,stand,start,state,stick,study,teach,thank,think,throw,touch
Data touch,train,treat,trust,visit,voice,waste,watch,worry,would,write
Data write,above,acute,alive,alone,angry,aware,awful,basic,black,blind
Data blind,brave,brief,broad,brown,cheap,chief,civil,clean,clear,close
Data close,crazy,daily,dirty,early,empty,equal,exact,extra,faint,false
Data false,fifth,final,first,fresh,front,funny,giant,grand,great,green
Data green,gross,happy,harsh,heavy,human,ideal,inner,joint,large,legal
Data legal,level,light,local,loose,lucky,magic,major,minor,moral,naked
Data naked,nasty,naval,other,outer,plain,prime,prior,proud,quick,quiet
Data quiet,rapid,ready,right,roman,rough,round,royal,rural,sharp,sheer
Data sheer,short,silly,sixth,small,smart,solid,sorry,spare,steep,still
Data still,super,sweet,thick,third,tight,total,tough,upper,upset,urban
Data urban,usual,vague,valid,vital,white,whole,wrong,young,afore,after
Data after,bothe,other,since,slash,until,where,while,aback,abaft,aboon
Data aboon,about,above,accel,adown,afoot,afore,afoul,after,again,agape
Data agape,agogo,agone,ahead,ahull,alife,alike,aline,aloft,alone,along
Data along,aloof,aloud,amiss,amply,amuck,apace,apart,aptly,arear,aside
Data aside,askew,awful,badly,bally,below,canny,cheap,clean,clear,coyly
Data coyly,daily,dimly,dirty,ditto,drily,dryly,dully,early,extra,false
Data false,fatly,feyly,first,fitly,forte,forth,fresh,fully,funny,gaily
Data gaily,gayly,godly,great,haply,heavy,hence,hotly,icily,infra
Data infra,jildi,jolly,laxly,lento,light,lowly,madly,maybe,never
Data never,newly,nobly,oddly,often,other,ought,party,piano,plain,plonk
Data plonk,plumb,prior,queer,quick,quite,ramen,rapid,redly,right,rough
Data rough,round,sadly,secus,selly,sharp,sheer,shily,short,shyly,silly
Data silly,since,sleek,slyly,small,sound,spang,stark,still
Data still,stone,stour,super,tally,tanto,there,thick,tight,today,tomoz
Data tomoz,truly,twice,under,utter,verry,wanly,wetly,where,wrong,wryly
Data wryly,abaft,aboon,about,above,adown,afore,after,along,aloof,among
Data among,below,circa,cross,furth,minus,neath,round,since,spite,under
Data under,until,aargh,adieu,adios,alack,aloha,avast,bakaw,basta,begad
Data begad,bless,blige,brava,bravo,bring,chook,damme,ditto,frick,fudge
Data fudge,golly,gratz,hallo,hasta,havoc,hello,howay,howdy,hullo
Data hullo,huzza,kapow,loose,marry,mercy,night,plonk,psych
Data psych,quite,salve,skoal,sniff,sooey,there,thiam,thwap,tough,twirp
Data twirp,viola,vivat,wacko,wahey,whist,wilma,wirra,woops,wowie,yecch
Data yecch,yeeha,yeesh,yowch,zowie
RE: 5 Letter Hangman - PhilOfPerth - 08-29-2022
I like it!
But for my littl'uns, the 4-letter will be enough, for now anyway.
By the way, for what it's worth, you set word=711 in line 23, then read 710 in line 25, then read another 1 in line 27.
If you read all 711 as word$() in line 23, you don't need the -1, or line 27. Maybe you have a reason why you did this but I can't see it.
RE: 5 Letter Hangman - SierraKen - 08-29-2022
Yes, I first get a random number from 1 to 711. Then I read all of them up to right before that random number. Then outside of the loop I read again and get the word that number matches. It works that way because the READ statement keeps going anywhere in the program until it is finished with all the DATA statements. I guess I could have done it a different way with just one READ statement with an IF/THEN statement. But this works fine too. I'm glad you like it.
RE: 5 Letter Hangman - bplus - 08-29-2022
Code: (Select All) _Title "5 Letter Hangman by Sierraken"
Randomize Timer ' <<< once up here is all that is needed
' read all the words into an array called words$(), do it once at start
Dim words$(1 To 711)
For w = 1 To 711
Read words$(w)
Next w
' check words
For i = 1 To 10
Print words$(i), words$(712 - i)
Next
Print "Checking load of first and last words, Press any to continue..."
Sleep
Code: (Select All) word$ = words$(Int(Rnd * 711) + 1) ' pick a random word (1 to 711) from words$() array
So now this:
Code: (Select All) '5 Letter Hangman by SierraKen - August 28, 2022.
'The game chooses between 711 5-letter words.
_Title "5 Letter Hangman by Sierraken"
Randomize Timer ' <<< once up here is all that is needed
' read all the words into an array called words$(), do it once at start
Dim words$(1 To 711)
For w = 1 To 711
Read words$(w)
Next w
' check words
For i = 1 To 10
Print words$(i), words$(712 - i)
Next
Print "Checking load of first and last words, Press any to continue..."
Sleep
start:
Cls
Screen _NewImage(800, 600, 32)
For y = 0 To 400
c = c + .5
Line (0, y)-(800, y), _RGB32(0, 0, c)
Next y
c = 0
Line (0, 400)-(800, 400), _RGB32(255, 255, 255)
Line (600, 400)-(600, 100), _RGB32(255, 255, 255)
Line (600, 100)-(400, 100), _RGB32(255, 255, 255)
Line (400, 100)-(400, 180), _RGB32(255, 255, 255)
For lines = 303 To 503 Step 50
Line (lines, 500)-(lines + 10, 500), _RGB32(255, 255, 255)
Next lines
word$ = words$(Int(Rnd * 711) + 1) ' pick a random word (1 to 711) from words$() array
letter1$ = Mid$(word$, 1, 1)
letter2$ = Mid$(word$, 2, 1)
letter3$ = Mid$(word$, 3, 1)
letter4$ = Mid$(word$, 4, 1)
letter5$ = Mid$(word$, 5, 1)
letter = 0: oldletter = 0: one = 0: two = 0: three = 0: four = 0: five = 0
mistake = 0
go:
Do
_Limit 20
a$ = InKey$
If a$ <> "" Then GoTo continue:
Loop
continue:
a$ = LCase$(a$)
If a$ = Chr$(27) Then End
oldletter = letter
If a$ = letter1$ Then
_PrintString (305, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
one = one + 1
If one = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter2$ Then
_PrintString (355, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
two = two + 1
If two = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter3$ Then
_PrintString (405, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
three = three + 1
If three = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter4$ Then
_PrintString (455, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
four = four + 1
If four = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter5$ Then
_PrintString (505, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
five = five + 1
If five = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If oldletter <> letter Then GoTo go:
mistake = mistake + 1
'Head
If mistake = 1 Then
Circle (400, 200), 20, _RGB32(255, 255, 255)
_PrintString (50, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Body
If mistake = 2 Then
Line (400, 220)-(400, 300), _RGB32(255, 255, 255)
_PrintString (75, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Arm
If mistake = 3 Then
Line (400, 240)-(375, 220), _RGB32(255, 255, 255)
_PrintString (100, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Arm
If mistake = 4 Then
Line (400, 240)-(425, 220), _RGB32(255, 255, 255)
_PrintString (125, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Leg
If mistake = 5 Then
Line (400, 300)-(370, 330), _RGB32(255, 255, 255)
_PrintString (150, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Leg
If mistake = 6 Then
Line (400, 300)-(430, 330), _RGB32(255, 255, 255)
_PrintString (50, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Eyes
If mistake = 7 Then
Circle (390, 190), 3, _RGB32(255, 255, 255)
Circle (410, 190), 3, _RGB32(255, 255, 255)
_PrintString (75, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Nose
If mistake = 8 Then
Circle (400, 200), 3, _RGB32(255, 255, 255)
_PrintString (100, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Mouth
If mistake = 9 Then
Circle (400, 212), 8, _RGB32(255, 255, 255), , , .5
_PrintString (125, 475), a$
For snd = 700 To 100 Step -50
Sound snd, .5
Next snd
_PrintString (305, 480), letter1$
_PrintString (355, 480), letter2$
_PrintString (405, 480), letter3$
_PrintString (455, 480), letter4$
_PrintString (505, 480), letter5$
_PrintString (305, 415), "You Lose!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
Restore
GoTo start:
End If
End
End If
GoTo go:
won:
_PrintString (305, 415), "You Win!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
Restore
GoTo start:
End If
End
Data abuse,adult,agent,anger,apple,award,basis,beach,birth,block,blood
Data blood,board,brain,bread,break,brown,buyer,cause,chain,chair,chest
Data chest,chief,child,china,claim,class,clock,coach,coast,court,cover
Data cover,cream,crime,cross,crowd,crown,cycle,dance,death,depth,doubt
Data doubt,draft,drama,dream,dress,drink,drive,earth,enemy,entry,error
Data error,event,faith,fault,field,fight,final,floor,focus,force,frame
Data frame,frank,front,fruit,glass,grant,grass,green,group,guide,heart
Data heart,henry,horse,hotel,house,image,index,input,issue,japan,jones
Data jones,judge,knife,laura,layer,level,lewis,light,limit,lunch,major
Data major,march,match,metal,model,money,month,motor,mouth,music,night
Data night,noise,north,novel,nurse,offer,order,other,owner,panel,paper
Data paper,party,peace,peter,phase,phone,piece,pilot,pitch,place,plane
Data plane,plant,plate,point,pound,power,press,price,pride,prize,proof
Data proof,queen,radio,range,ratio,reply,right,river,round,route,rugby
Data rugby,scale,scene,scope,score,sense,shape,share,sheep,sheet,shift
Data shift,shirt,shock,sight,simon,skill,sleep,smile,smith,smoke,sound
Data sound,south,space,speed,spite,sport,squad,staff,stage,start,state
Data state,steam,steel,stock,stone,store,study,stuff,style,sugar,table
Data table,taste,terry,theme,thing,title,total,touch,tower,track,trade
Data trade,train,trend,trial,trust,truth,uncle,union,unity,value,video
Data video,visit,voice,waste,watch,water,while,white,whole,woman,world
Data world,youth,there,where,which,whose,whoso,yours,yours,admit
Data admit,adopt,agree,allow,alter,apply,argue,arise,avoid,begin,blame
Data blame,break,bring,build,burst,carry,catch,cause,check,claim,clean
Data clean,clear,climb,close,count,cover,cross,dance,doubt,drink,drive
Data drive,enjoy,enter,exist,fight,focus,force,guess,imply,issue,judge
Data judge,laugh,learn,leave,limit,marry,match,occur,offer,order
Data order,phone,place,point,press,prove,raise,reach,refer,relax,serve
Data serve,shall,share,shift,shoot,sleep,solve,sound,speak,spend,split
Data split,stand,start,state,stick,study,teach,thank,think,throw,touch
Data touch,train,treat,trust,visit,voice,waste,watch,worry,would,write
Data write,above,acute,alive,alone,angry,aware,awful,basic,black,blind
Data blind,brave,brief,broad,brown,cheap,chief,civil,clean,clear,close
Data close,crazy,daily,dirty,early,empty,equal,exact,extra,faint,false
Data false,fifth,final,first,fresh,front,funny,giant,grand,great,green
Data green,gross,happy,harsh,heavy,human,ideal,inner,joint,large,legal
Data legal,level,light,local,loose,lucky,magic,major,minor,moral,naked
Data naked,nasty,naval,other,outer,plain,prime,prior,proud,quick,quiet
Data quiet,rapid,ready,right,roman,rough,round,royal,rural,sharp,sheer
Data sheer,short,silly,sixth,small,smart,solid,sorry,spare,steep,still
Data still,super,sweet,thick,third,tight,total,tough,upper,upset,urban
Data urban,usual,vague,valid,vital,white,whole,wrong,young,afore,after
Data after,bothe,other,since,slash,until,where,while,aback,abaft,aboon
Data aboon,about,above,accel,adown,afoot,afore,afoul,after,again,agape
Data agape,agogo,agone,ahead,ahull,alife,alike,aline,aloft,alone,along
Data along,aloof,aloud,amiss,amply,amuck,apace,apart,aptly,arear,aside
Data aside,askew,awful,badly,bally,below,canny,cheap,clean,clear,coyly
Data coyly,daily,dimly,dirty,ditto,drily,dryly,dully,early,extra,false
Data false,fatly,feyly,first,fitly,forte,forth,fresh,fully,funny,gaily
Data gaily,gayly,godly,great,haply,heavy,hence,hotly,icily,infra
Data infra,jildi,jolly,laxly,lento,light,lowly,madly,maybe,never
Data never,newly,nobly,oddly,often,other,ought,party,piano,plain,plonk
Data plonk,plumb,prior,queer,quick,quite,ramen,rapid,redly,right,rough
Data rough,round,sadly,secus,selly,sharp,sheer,shily,short,shyly,silly
Data silly,since,sleek,slyly,small,sound,spang,stark,still
Data still,stone,stour,super,tally,tanto,there,thick,tight,today,tomoz
Data tomoz,truly,twice,under,utter,verry,wanly,wetly,where,wrong,wryly
Data wryly,abaft,aboon,about,above,adown,afore,after,along,aloof,among
Data among,below,circa,cross,furth,minus,neath,round,since,spite,under
Data under,until,aargh,adieu,adios,alack,aloha,avast,bakaw,basta,begad
Data begad,bless,blige,brava,bravo,bring,chook,damme,ditto,frick,fudge
Data fudge,golly,gratz,hallo,hasta,havoc,hello,howay,howdy,hullo
Data hullo,huzza,kapow,loose,marry,mercy,night,plonk,psych
Data psych,quite,salve,skoal,sniff,sooey,there,thiam,thwap,tough,twirp
Data twirp,viola,vivat,wacko,wahey,whist,wilma,wirra,woops,wowie,yecch
Data yecch,yeeha,yeesh,yowch,zowie
RE: 5 Letter Hangman - SierraKen - 08-29-2022
Thanks B+ . What didn't work though was adding SLEEP because when I pressed any key to get out of SLEEP, it used that key press as my first choice in the game.
So instead I used INPUT to press Enter to start the game after your DATA check. I really like how you put all the words in an array first and then people can play as much as they want without having to read the DATA again. I also removed the unneeded RESTORE commands for when people play again. This morning I also wondered about the Randomize Timer location, am glad you changed it.
Code: (Select All) '5 Letter Hangman by SierraKen - August 28, 2022.
'The game chooses between 711 5-letter words.
_Title "5 Letter Hangman by Sierraken"
Randomize Timer ' <<< once up here is all that is needed
' read all the words into an array called words$(), do it once at start
Dim words$(1 To 711)
For w = 1 To 711
Read words$(w)
Next w
Print "Checking load of first and last words..."
Print
' check words
For i = 1 To 10
Print words$(i), words$(712 - i)
Next
Print
Input "Press Enter to start game.", e$
start:
Cls
Screen _NewImage(800, 600, 32)
For y = 0 To 400
c = c + .5
Line (0, y)-(800, y), _RGB32(0, 0, c)
Next y
c = 0
Line (0, 400)-(800, 400), _RGB32(255, 255, 255)
Line (600, 400)-(600, 100), _RGB32(255, 255, 255)
Line (600, 100)-(400, 100), _RGB32(255, 255, 255)
Line (400, 100)-(400, 180), _RGB32(255, 255, 255)
For lines = 303 To 503 Step 50
Line (lines, 500)-(lines + 10, 500), _RGB32(255, 255, 255)
Next lines
word$ = words$(Int(Rnd * 711) + 1) ' pick a random word (1 to 711) from words$() array
letter1$ = Mid$(word$, 1, 1)
letter2$ = Mid$(word$, 2, 1)
letter3$ = Mid$(word$, 3, 1)
letter4$ = Mid$(word$, 4, 1)
letter5$ = Mid$(word$, 5, 1)
letter = 0: oldletter = 0: one = 0: two = 0: three = 0: four = 0: five = 0
mistake = 0
go:
Do
_Limit 20
a$ = InKey$
If a$ <> "" Then GoTo continue:
Loop
continue:
a$ = LCase$(a$)
If a$ = Chr$(27) Then End
oldletter = letter
If a$ = letter1$ Then
_PrintString (305, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
one = one + 1
If one = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter2$ Then
_PrintString (355, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
two = two + 1
If two = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter3$ Then
_PrintString (405, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
three = three + 1
If three = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter4$ Then
_PrintString (455, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
four = four + 1
If four = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If a$ = letter5$ Then
_PrintString (505, 480), a$
For snd = 200 To 700 Step 100
Sound snd, .5
Next snd
five = five + 1
If five = 1 Then letter = letter + 1
If letter = 5 Then GoTo won:
End If
If oldletter <> letter Then GoTo go:
mistake = mistake + 1
'Head
If mistake = 1 Then
Circle (400, 200), 20, _RGB32(255, 255, 255)
_PrintString (50, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Body
If mistake = 2 Then
Line (400, 220)-(400, 300), _RGB32(255, 255, 255)
_PrintString (75, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Arm
If mistake = 3 Then
Line (400, 240)-(375, 220), _RGB32(255, 255, 255)
_PrintString (100, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Arm
If mistake = 4 Then
Line (400, 240)-(425, 220), _RGB32(255, 255, 255)
_PrintString (125, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Left Leg
If mistake = 5 Then
Line (400, 300)-(370, 330), _RGB32(255, 255, 255)
_PrintString (150, 450), a$
Sound 200, .5
Sound 600, .5
End If
'Right Leg
If mistake = 6 Then
Line (400, 300)-(430, 330), _RGB32(255, 255, 255)
_PrintString (50, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Eyes
If mistake = 7 Then
Circle (390, 190), 3, _RGB32(255, 255, 255)
Circle (410, 190), 3, _RGB32(255, 255, 255)
_PrintString (75, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Nose
If mistake = 8 Then
Circle (400, 200), 3, _RGB32(255, 255, 255)
_PrintString (100, 475), a$
Sound 200, .5
Sound 600, .5
End If
'Mouth
If mistake = 9 Then
Circle (400, 212), 8, _RGB32(255, 255, 255), , , .5
_PrintString (125, 475), a$
For snd = 700 To 100 Step -50
Sound snd, .5
Next snd
_PrintString (305, 480), letter1$
_PrintString (355, 480), letter2$
_PrintString (405, 480), letter3$
_PrintString (455, 480), letter4$
_PrintString (505, 480), letter5$
_PrintString (305, 415), "You Lose!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
GoTo start:
End If
End
End If
GoTo go:
won:
_PrintString (305, 415), "You Win!"
Locate 29, 38: Input "Again (Y/N)"; ag$
If Mid$(ag$, 1, 1) = "y" Or Mid$(ag$, 1, 1) = "Y" Then
GoTo start:
End If
End
Data abuse,adult,agent,anger,apple,award,basis,beach,birth,block,blood
Data blood,board,brain,bread,break,brown,buyer,cause,chain,chair,chest
Data chest,chief,child,china,claim,class,clock,coach,coast,court,cover
Data cover,cream,crime,cross,crowd,crown,cycle,dance,death,depth,doubt
Data doubt,draft,drama,dream,dress,drink,drive,earth,enemy,entry,error
Data error,event,faith,fault,field,fight,final,floor,focus,force,frame
Data frame,frank,front,fruit,glass,grant,grass,green,group,guide,heart
Data heart,henry,horse,hotel,house,image,index,input,issue,japan,jones
Data jones,judge,knife,laura,layer,level,lewis,light,limit,lunch,major
Data major,march,match,metal,model,money,month,motor,mouth,music,night
Data night,noise,north,novel,nurse,offer,order,other,owner,panel,paper
Data paper,party,peace,peter,phase,phone,piece,pilot,pitch,place,plane
Data plane,plant,plate,point,pound,power,press,price,pride,prize,proof
Data proof,queen,radio,range,ratio,reply,right,river,round,route,rugby
Data rugby,scale,scene,scope,score,sense,shape,share,sheep,sheet,shift
Data shift,shirt,shock,sight,simon,skill,sleep,smile,smith,smoke,sound
Data sound,south,space,speed,spite,sport,squad,staff,stage,start,state
Data state,steam,steel,stock,stone,store,study,stuff,style,sugar,table
Data table,taste,terry,theme,thing,title,total,touch,tower,track,trade
Data trade,train,trend,trial,trust,truth,uncle,union,unity,value,video
Data video,visit,voice,waste,watch,water,while,white,whole,woman,world
Data world,youth,there,where,which,whose,whoso,yours,yours,admit
Data admit,adopt,agree,allow,alter,apply,argue,arise,avoid,begin,blame
Data blame,break,bring,build,burst,carry,catch,cause,check,claim,clean
Data clean,clear,climb,close,count,cover,cross,dance,doubt,drink,drive
Data drive,enjoy,enter,exist,fight,focus,force,guess,imply,issue,judge
Data judge,laugh,learn,leave,limit,marry,match,occur,offer,order
Data order,phone,place,point,press,prove,raise,reach,refer,relax,serve
Data serve,shall,share,shift,shoot,sleep,solve,sound,speak,spend,split
Data split,stand,start,state,stick,study,teach,thank,think,throw,touch
Data touch,train,treat,trust,visit,voice,waste,watch,worry,would,write
Data write,above,acute,alive,alone,angry,aware,awful,basic,black,blind
Data blind,brave,brief,broad,brown,cheap,chief,civil,clean,clear,close
Data close,crazy,daily,dirty,early,empty,equal,exact,extra,faint,false
Data false,fifth,final,first,fresh,front,funny,giant,grand,great,green
Data green,gross,happy,harsh,heavy,human,ideal,inner,joint,large,legal
Data legal,level,light,local,loose,lucky,magic,major,minor,moral,naked
Data naked,nasty,naval,other,outer,plain,prime,prior,proud,quick,quiet
Data quiet,rapid,ready,right,roman,rough,round,royal,rural,sharp,sheer
Data sheer,short,silly,sixth,small,smart,solid,sorry,spare,steep,still
Data still,super,sweet,thick,third,tight,total,tough,upper,upset,urban
Data urban,usual,vague,valid,vital,white,whole,wrong,young,afore,after
Data after,bothe,other,since,slash,until,where,while,aback,abaft,aboon
Data aboon,about,above,accel,adown,afoot,afore,afoul,after,again,agape
Data agape,agogo,agone,ahead,ahull,alife,alike,aline,aloft,alone,along
Data along,aloof,aloud,amiss,amply,amuck,apace,apart,aptly,arear,aside
Data aside,askew,awful,badly,bally,below,canny,cheap,clean,clear,coyly
Data coyly,daily,dimly,dirty,ditto,drily,dryly,dully,early,extra,false
Data false,fatly,feyly,first,fitly,forte,forth,fresh,fully,funny,gaily
Data gaily,gayly,godly,great,haply,heavy,hence,hotly,icily,infra
Data infra,jildi,jolly,laxly,lento,light,lowly,madly,maybe,never
Data never,newly,nobly,oddly,often,other,ought,party,piano,plain,plonk
Data plonk,plumb,prior,queer,quick,quite,ramen,rapid,redly,right,rough
Data rough,round,sadly,secus,selly,sharp,sheer,shily,short,shyly,silly
Data silly,since,sleek,slyly,small,sound,spang,stark,still
Data still,stone,stour,super,tally,tanto,there,thick,tight,today,tomoz
Data tomoz,truly,twice,under,utter,verry,wanly,wetly,where,wrong,wryly
Data wryly,abaft,aboon,about,above,adown,afore,after,along,aloof,among
Data among,below,circa,cross,furth,minus,neath,round,since,spite,under
Data under,until,aargh,adieu,adios,alack,aloha,avast,bakaw,basta,begad
Data begad,bless,blige,brava,bravo,bring,chook,damme,ditto,frick,fudge
Data fudge,golly,gratz,hallo,hasta,havoc,hello,howay,howdy,hullo
Data hullo,huzza,kapow,loose,marry,mercy,night,plonk,psych
Data psych,quite,salve,skoal,sniff,sooey,there,thiam,thwap,tough,twirp
Data twirp,viola,vivat,wacko,wahey,whist,wilma,wirra,woops,wowie,yecch
Data yecch,yeeha,yeesh,yowch,zowie
RE: 5 Letter Hangman - SierraKen - 08-29-2022
I also didn't know that you can use a string without the array attached after it's already had an array variable. Very cool!
Edit: Woops I see what you did, you changed the word$ to make it without an array with the RND, so technically it's a totally different string after that.
RE: 5 Letter Hangman - bplus - 08-29-2022
Yes! very good, I picked up on that problem with SLEEP key press as being the first "Letter" pressed and the hanging started right after seeing the array load check. Yikes! I just dumped the check. I had it in there so you or I would be reassured the array of Words$() did load from first to last correctly.
Yes word$ is just one from words$(), I guess the s is kind of hard to see next to $.
I made more changes just to see how many lines I could eliminate... 186 with all the words included.
At first I thought you oldLetters was checking if you were repeating a Letter guessed already, but no, it's to compare to Letters to see if any new hits, if not a "mistake".
Might be good idea to see if repeating an old letter, might declare a false win by repeating same successful letter 5 times. (OK no that doesn't happen.)
RE: 5 Letter Hangman - SierraKen - 08-29-2022
Thanks. Yes exactly, OldLetter is used to go back to the beginning if there's no mistake. I think I've tried every possibility. Like if you choose 1 o and there's 2 o's it will place both of them at once. If you accidentally repeat a mistake, it will still count as another mistake. Or if you repeat a letter that wasn't a mistake, but it's not needed, it will also count as a mistake.
I think I'm going go see if I can learn how to stop a READ command on any amount of DATA so people can add and delete any 5 letter words they wish. I don't even know if it's possible. But I'll make a new app for that to play around with first.
RE: 5 Letter Hangman - SierraKen - 08-29-2022
Sweet I can use on error goto, kinda like this.
Code: (Select All) Do
On Error GoTo nomore:
Read a$
Print a$
Loop
nomore:
Data one,two,three,four
Data five,six,seven,eight
Data nine,ten,eleven,twelve
RE: 5 Letter Hangman - SierraKen - 08-29-2022
Oh shoot, I can't do that because I need a set number to DIM the array with. Oh well.
Edit: I did it! Go to the next page to see.
|