5 Letter Hangman
#14
Like I found in Hangman 2, there's a DATA lines issue on this one where the last word doubles up on the next line. So I fixed it. And instead of 711 words there's 654.
Please try Hangman 2 on the other thread as well, because it uses 1000 words from 2 letters to 12 letters. Smile 

Code: (Select All)
'5 Letter Hangman by SierraKen - August 28, 2022.
'The game chooses between 654 5-letter words.
'Feel free to add or subtract any 5 letter words from the DATA lines. This program will count them.

_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
Do
    On Error GoTo readagain:
    Read words$
    w = w + 1
Loop
readagain:
Restore ManyWords:
Dim words$(w)
For a = 1 To w
    Read words$(a)
Next a

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 * w) + 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

ManyWords:
Data abuse,adult,agent,anger,apple,award,basis,beach,birth,block
Data blood,board,brain,bread,break,brown,buyer,cause,chain,chair
Data chest,chief,child,china,claim,class,clock,coach,coast,court
Data cover,cream,crime,cross,crowd,crown,cycle,dance,death,depth
Data doubt,draft,drama,dream,dress,drink,drive,earth,enemy,entry
Data error,event,faith,fault,field,fight,final,floor,focus,force
Data frame,frank,front,fruit,glass,grant,grass,green,group,guide
Data heart,henry,horse,hotel,house,image,index,input,issue,japan
Data jones,judge,knife,laura,layer,level,lewis,light,limit,lunch
Data major,march,match,metal,model,money,month,motor,mouth,music
Data night,noise,north,novel,nurse,offer,order,other,owner,panel
Data paper,party,peace,peter,phase,phone,piece,pilot,pitch,place
Data plane,plant,plate,point,pound,power,press,price,pride,prize
Data proof,queen,radio,range,ratio,reply,right,river,round,route
Data rugby,scale,scene,scope,score,sense,shape,share,sheep,sheet
Data shift,shirt,shock,sight,simon,skill,sleep,smile,smith,smoke
Data sound,south,space,speed,spite,sport,squad,staff,stage,start
Data state,steam,steel,stock,stone,store,study,stuff,style,sugar
Data table,taste,terry,theme,thing,title,total,touch,tower,track
Data trade,train,trend,trial,trust,truth,uncle,union,unity,value
Data video,visit,voice,waste,watch,water,while,white,whole,woman
Data world,youth,there,where,which,whose,whoso,yours,yours,admit
Data adopt,agree,allow,alter,apply,argue,arise,avoid,begin,blame
Data break,bring,build,burst,carry,catch,cause,check,claim,clean
Data clear,climb,close,count,cover,cross,dance,doubt,drink,drive
Data enjoy,enter,exist,fight,focus,force,guess,imply,issue,judge
Data laugh,learn,leave,let’s,limit,marry,match,occur,offer,order
Data phone,place,point,press,prove,raise,reach,refer,relax,serve
Data shall,share,shift,shoot,sleep,solve,sound,speak,spend,split
Data stand,start,state,stick,study,teach,thank,think,throw,touch
Data train,treat,trust,visit,voice,waste,watch,worry,would,write
Data above,acute,alive,alone,angry,aware,awful,basic,black,blind
Data brave,brief,broad,brown,cheap,chief,civil,clean,clear,close
Data crazy,daily,dirty,early,empty,equal,exact,extra,faint,false
Data fifth,final,first,fresh,front,funny,giant,grand,great,green
Data gross,happy,harsh,heavy,human,ideal,inner,joint,large,legal
Data level,light,local,loose,lucky,magic,major,minor,moral,naked
Data nasty,naval,other,outer,plain,prime,prior,proud,quick,quiet
Data rapid,ready,right,roman,rough,round,royal,rural,sharp,sheer
Data short,silly,sixth,small,smart,solid,sorry,spare,steep,still
Data super,sweet,thick,third,tight,total,tough,upper,upset,urban
Data usual,vague,valid,vital,white,whole,wrong,young,afore,after
Data bothe,other,since,slash,until,where,while,aback,abaft,aboon
Data about,above,accel,adown,afoot,afore,afoul,after,again,agape
Data agogo,agone,ahead,ahull,alife,alike,aline,aloft,alone,along
Data aloof,aloud,amiss,amply,amuck,apace,apart,aptly,arear,aside
Data askew,awful,badly,bally,below,canny,cheap,clean,clear,coyly
Data daily,dimly,dirty,ditto,drily,dryly,dully,early,extra,false
Data fatly,feyly,first,fitly,forte,forth,fresh,fully,funny,gaily
Data gayly,godly,great,haply,heavy,hella,hence,hotly,icily,infra
Data intl.,jildi,jolly,laxly,lento,light,lowly,madly,maybe,never
Data newly,nobly,oddly,often,other,ought,party,piano,plain,plonk
Data plumb,prior,queer,quick,quite,ramen,rapid,redly,right,rough
Data round,sadly,secus,selly,sharp,sheer,shily,short,shyly,silly
Data since,sleek,slyly,small,so-so,sound,spang,srsly,stark,still
Data stone,stour,super,tally,tanto,there,thick,tight,today,tomoz
Data truly,twice,under,utter,verry,wanly,wetly,where,wrong,wryly
Data abaft,aboon,about,above,adown,afore,after,along,aloof,among
Data below,circa,cross,furth,minus,neath,round,since,spite,under
Data until,aargh,adieu,adios,alack,aloha,avast,bakaw,basta,begad
Data bless,blige,brava,bravo,bring,chook,damme,ditto,frick,fudge
Data golly,gratz,hallo,hasta,havoc,hella,hello,howay,howdy,hullo
Data huzza,jesus,kapow,loose,lordy,marry,mercy,night,plonk,psych
Data quite,salve,skoal,sniff,sooey,there,thiam,thwap,tough,twirp
Data viola,vivat,wacko,wahey,whist,wilma,wirra,woops,wowie,yecch
Data yeeha,yeesh,yowch,zowie
Reply


Messages In This Thread
5 Letter Hangman - by SierraKen - 08-29-2022, 06:17 AM
RE: 5 Letter Hangman - by PhilOfPerth - 08-29-2022, 06:46 AM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 04:21 PM
RE: 5 Letter Hangman - by bplus - 08-29-2022, 05:27 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 06:30 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 06:36 PM
RE: 5 Letter Hangman - by bplus - 08-29-2022, 07:21 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 09:03 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 09:08 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 09:11 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 09:31 PM
RE: 5 Letter Hangman - by bplus - 08-29-2022, 09:56 PM
RE: 5 Letter Hangman - by SierraKen - 08-29-2022, 10:57 PM
RE: 5 Letter Hangman - by SierraKen - 08-30-2022, 08:23 PM
RE: 5 Letter Hangman - by bplus - 08-30-2022, 09:07 PM
RE: 5 Letter Hangman - by SierraKen - 08-30-2022, 09:28 PM



Users browsing this thread: 6 Guest(s)