Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
Hangman 2 with 2 to 12 letter words!
#11
That gallows looks a little rickity...

Code: (Select All)
'Hangman 2 by SierraKen - August 30, 2022.
'Thanks to B+ for some guidance.
'----------------------------------------------------------------------------------------------------
'Feel free to add or subtract any words from the DATA lines with letter amounts two to twelve.
'If you accidentally add a word larger than 12 letters or smaller than 2 letters, it will not use it.
'Also if you accidentally add a word with a capital letter or a symbol, it won't use that either.
'1000 common words comes with this on the DATA lines of different sizes.

_TITLE "Hangman 2 by Sierraken"
RANDOMIZE TIMER ' <<< once up here is all that is needed

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

DIM letter$(30), letter2$(30)

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) 'ground

'a little beefier carpentry
FOR beam% = 0 TO 19
    IF beam% MOD 2 = 0 THEN c~& = &HFF964B00 ELSE c~& = &HFF7F7F7F
    LINE (600 - beam%, 400)-(600 - beam%, 100 + beam%), c~& 'vertical post
    LINE (600 - beam%, 100 + beam%)-(400 + beam, 100 + beam%), c~& 'horizontal post
NEXT beam%
LINE (400, 100)-(400, 180), _RGB32(255, 255, 255)

randword:
word$ = words$(INT(RND * w) + 1)
l = LEN(word$)
IF l > 12 OR l < 2 THEN GOTO randword:

FOR lines = 203 TO 203 + ((l - 1) * 50) STEP 50
    LINE (lines, 500)-(lines + 10, 500), _RGB32(255, 255, 255)
NEXT lines

FOR ll = 1 TO l
    letter$(ll) = MID$(word$, ll, 1)
    IF ASC(letter$(ll)) < 97 OR ASC(letter$(ll)) > 122 THEN GOTO start:
    letter2$(ll) = letter$(ll)
NEXT ll
letter = 0: oldletter = 0
mistake = 0: t = 1

go:

g = 0
DO
    _LIMIT 20
    a$ = INKEY$
    IF a$ <> "" THEN GOTO continue:
LOOP

continue:
a$ = LCASE$(a$)
IF a$ = CHR$(27) THEN END
t = t + 1
oldletter = letter
FOR ll = 1 TO l
    IF a$ = letter$(ll) THEN
        IF g < 1 THEN letter$(ll) = ""
        g = 1
        letter = letter + 1
        _PRINTSTRING (205 + (ll - 1) * 50, 480), a$
        FOR snd = 200 TO 700 STEP 100
            SOUND snd, .5
        NEXT snd
        IF letter = l THEN GOTO won:
    END IF
NEXT ll


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
    FOR ll = 1 TO l
        _PRINTSTRING (205 + (ll - 1) * 50, 480), letter2$(ll)
    NEXT ll
    _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!"
FOR s = 1 TO 2
    FOR snd = 100 TO 800 STEP 100
        SOUND snd, .5
    NEXT snd
NEXT s
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

'Almost all of the following words were found here: https://www.ef.edu/english-resources/english-vocabulary/top-1000-words/
ManyWords:
DATA ability,able,about,above,accept,according,account,across,act,action
DATA activity,actually,add,address,administration,admit,adult,affect,after,again
DATA against,age,agency,agent,ago,agree,agreement,ahead,air,all
DATA allow,almost,alone,along,already,also,although,always,among,amount
DATA analysis,and,animal,another,answer,any,anyone,anything,appear,apply
DATA approach,area,argue,arm,around,arrive,art,article,artist,as
DATA ask,assume,at,attack,attention,attorney,audience,author,authority,available
DATA avoid,away,baby,back,bad,bag,ball,bank,bar,base
DATA be,bear,beat,beautiful,because,become,bed,before,begin,behavior
DATA behind,believe,benefit,best,better,between,beyond,big,bill,billion
DATA bit,black,blood,blue,board,body,book,born,both,box
DATA boy,break,bring,brother,budget,build,building,business,but,buy
DATA by,call,camera,campaign,can,cancer,candidate,capital,car,card
DATA care,career,carry,case,cat,catch,cause,cell,center,central
DATA century,certain,certainly,chair,challenge,chance,change,character,charge,check
DATA child,choice,choose,church,citizen,city,civil,claim,class,clear
DATA clearly,close,coach,cold,collection,college,color,come,commercial,common
DATA community,company,compare,computer,concern,condition,conference,consider,consumer,contain
DATA continue,control,cost,could,country,couple,course,court,cover,cow
DATA create,crime,cultural,culture,cup,current,customer,cut,dark,data
DATA daughter,day,dead,deal,death,debate,decade,decide,decision,deep
DATA defense,degree,democratic,describe,design,despite,detail,determine,develop,development
DATA die,difference,different,difficult,dinner,dinosaur,direction,director,discover,discuss
DATA discussion,disease,do,doctor,dog,door,down,draw,dream,drive
DATA drop,drug,during,each,early,east,easy,eat,economic,economy
DATA edge,education,effect,effort,eight,either,election,elephant,else,employee
DATA end,energy,enjoy,enough,enter,entire,environment,especially,establish,even
DATA evening,event,ever,every,everybody,everyone,everything,evidence,exactly,example
DATA executive,exist,expect,experience,expert,explain,eye,face,fact,factor
DATA fail,fall,family,far,fast,father,fear,federal,feel,feeling
DATA few,field,fight,figure,fill,film,final,finally,financial,find
DATA fine,finger,finish,fire,firm,first,fish,five,floor,fly
DATA focus,follow,food,foot,for,force,foreign,forget,form,former
DATA forward,four,free,friend,from,front,full,fund,future,game
DATA garden,gas,general,generation,get,girl,give,glass,go,goal
DATA good,government,great,green,ground,group,grow,growth,guess,gun
DATA guy,hair,half,hand,hang,happen,happy,hard,have,he
DATA head,health,hear,heart,heat,heavy,help,her,here,herself
DATA high,him,himself,his,history,hit,hold,home,hope,horse
DATA hospital,hot,hotel,hour,house,how,however,huge,human,hundred
DATA husband,idea,identify,if,image,imagine,impact,important,improve,in
DATA include,including,increase,indeed,indicate,individual,industry,information,inside,instead
DATA institution,interest,interesting,interview,into,investment,involve,issue,it,item
DATA its,itself,job,join,just,keep,key,kid,kill,kind
DATA kitchen,know,knowledge,land,language,large,last,late,later,laugh
DATA law,lawyer,lay,lead,leader,learn,least,leave,left,leg
DATA legal,less,let,letter,level,lie,life,light,like,likely
DATA line,list,listen,little,live,local,long,look,lose,loss
DATA lot,love,low,machine,magazine,main,maintain,major,majority,make
DATA man,manage,management,manager,many,market,marriage,material,matter,may
DATA maybe,me,mean,measure,meat,media,medical,meet,meeting,member
DATA memory,mention,message,method,middle,might,military,million,mind,minute
DATA miss,mission,model,modern,moment,money,month,more,morning,most
DATA mother,mouth,move,movement,movie,much,music,must,my,myself
DATA name,nation,national,natural,nature,near,nearly,necessary,need,network
DATA never,new,news,newspaper,next,nice,night,no,none,nor
DATA north,not,note,nothing,notice,now,number,occur,of,off
DATA offer,office,officer,official,often,oh,oil,ok,old,on
DATA once,one,only,onto,open,operation,opportunity,option,or,order
DATA organization,other,others,our,out,outside,over,own,owner,page
DATA pain,painting,paper,parent,part,participant,particular,particularly,partner,party
DATA pass,past,patient,pattern,pay,peace,people,per,perform,performance
DATA perhaps,period,person,personal,phone,physical,pick,picture,piece,pig
DATA place,plan,plant,play,player,PM,point,police,policy,political
DATA politics,poor,popular,population,position,positive,possible,power,practice,prepare
DATA present,president,pressure,pretty,prevent,price,private,probably,problem,process
DATA produce,product,production,professional,professor,program,project,property,protect,prove
DATA provide,public,pull,purpose,push,put,quality,question,quickly,quite
DATA race,radio,raise,range,rate,rather,reach,read,ready,real
DATA reality,realize,really,reason,receive,recent,recently,recognize,record,red
DATA reduce,reflect,region,relate,relationship,religious,remain,remember,remove,report
DATA represent,require,research,resource,respond,response,rest,result,return,reveal
DATA rich,right,rise,risk,road,rock,role,room,rule,run
DATA safe,same,save,say,scene,school,science,scientist,score,sea
DATA season,seat,second,section,security,see,seek,seem,sell,send
DATA senior,sense,series,serious,serve,service,set,seven,several,sex
DATA sexual,shake,share,she,shoot,short,shot,should,shoulder,show
DATA side,sign,significant,similar,simple,simply,since,sing,single,sister
DATA sit,site,situation,six,size,skill,skin,small,smile,so
DATA social,society,soldier,some,somebody,someone,something,sometimes,son,song
DATA soon,sort,sound,source,south,southern,space,speak,special,specific
DATA speech,spend,sport,spring,staff,stage,stand,standard,star,start
DATA state,statement,station,stay,step,still,stock,stop,store,story
DATA strategy,street,strong,structure,student,study,stuff,style,subject,success
DATA successful,such,suddenly,suffer,suggest,summer,support,sure,surface,system
DATA table,take,talk,task,tax,teach,teacher,team,technology,telephone
DATA television,tell,ten,tend,term,test,than,thank,that,the
DATA their,them,themselves,then,theory,there,these,they,thing,think
DATA third,this,those,though,thought,thousand,threat,three,through,throughout
DATA throw,thus,time,to,today,together,tonight,too,top,total
DATA tough,toward,town,trade,traditional,training,travel,treat,treatment,tree
DATA trial,trip,trouble,truck,true,truth,try,turn,two,type
DATA under,understand,unit,until,up,upon,us,use,usually,value
DATA various,very,victim,view,violence,visit,voice,vote,wait,walk
DATA wall,want,war,watch,water,way,we,weapon,wear,week
DATA weight,well,west,western,what,whatever,when,where,whether,which
DATA while,white,who,whole,whom,whose,why,wide,wife,will
DATA win,wind,window,wish,with,within,without,woman,wonder,word
DATA work,worker,world,worry,would,write,writer,wrong,xylophone,yard
DATA yeah,year,yes,yet,you,young,your,yourself,zebra,zoo
DO: LOOP: DO: LOOP
sha_na_na_na_na_na_na_na_na_na:
Reply
#12
Phil, you can add any words you want (2 to 12 letters) to the DATA statements, or even add a DATA statement line and it will use it. But if it ever randomly picks it is another deal, it would be 1 out of 1001 chance. Unless of course you can also delete as many as you want too. lol
Edit: I added monotonous to it below. Smile
Reply
#13
LOL Thanks OldMoses! But you didn't use my updated version with more colors and the cement foundation. I'll add what you made to it.....
Phil, I added monotonous to it too. Smile 

There we go:

(Code deleted, there's a better looking one after this post.)
Reply
#14
OK guys, I went all out and re-designed the Hangman guy and made much better grass. I also put white boxes around each letter so the letters stand out better. Here is a picture of it too.
Please tell me what you think, thanks.


[Image: Hangman-2-by-Sierra-Ken.jpg]

(Code deleted, scroll down to the next code.)
Reply
#15
Looking good. Everything you need but the tumbleweeds.
DO: LOOP: DO: LOOP
sha_na_na_na_na_na_na_na_na_na:
Reply
#16
Love it! Great work Ken.
One small tweak you may like to make: the "Again (Y/N)" box may look nicer if you add a space before the text:" Again (Y/N)" and re-centre it.
Now excuse me, I have an appointment with the Hangman!
Of all the places on Earth, and all the planets in the Universe, I'd rather live here (Perth, W.A.) Big Grin
Please visit my Website at: http://oldendayskids.blogspot.com/
Reply
#17
Thanks you 2. I added some shrubs on the horizon and did what you asked Phil and made some white space around the Again and You Win and You Lose text. Click the picture to see the whole thing.


[Image: Hangman-2-by-Sierra-Ken.jpg]



Code: (Select All)
'Hangman 2 by SierraKen - August 30, 2022.
'Thanks to B+ for some guidance and OldMoses for a better looking gallows.
'----------------------------------------------------------------------------------------------------
'Feel free to add or subtract any words from the DATA lines with letter amounts two to twelve.
'If you accidentally add a word larger than 12 letters or smaller than 2 letters, it will not use it.
'Also if you accidentally add a word with a capital letter or a symbol, it won't use that either.
'1000 common words comes with this on the DATA lines of different sizes.

_Title "Hangman 2 by Sierraken"
Randomize Timer ' <<< once up here is all that is needed

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

Dim letter$(30), letter2$(30)

start:
Cls
Screen _NewImage(800, 600, 32)

'Sky
For y = 0 To 400
    c = c + .5
    Line (0, y)-(800, y), _RGB32(0, 0, c)
Next y
c = 0
'Grass
For y = 401 To 600
    c = c + .5
    Line (0, y)-(800, y), _RGB32(0, c, 0)
Next y
c = 0
'Tumbleweeds
For weeds = 50 To 500 Step 100
    For seconds = 0 To 15 Step 4
        s = (60 - seconds) * 6 + 180
        x = Int(Sin(s / 180 * 3.141592) * 60) + weeds
        y = Int(Cos(s / 180 * 3.141592) * 60) + 401
        For b = .7 To -.7 Step -.1
            Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
            Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
        Next b
    Next seconds
    For seconds = 45 To 60 Step 4
        s = (60 - seconds) * 6 + 180
        x = Int(Sin(s / 180 * 3.141592) * 60) + weeds
        y = Int(Cos(s / 180 * 3.141592) * 60) + 401
        For b = .7 To -.7 Step -.1
            Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
            Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
        Next b
    Next seconds
Next weeds
For weeds = 50 To 500 Step 100
    For seconds = 0 To 15 Step 2
        s = (60 - seconds) * 6 + 180
        x = Int(Sin(s / 180 * 3.141592) * 30) + weeds
        y = Int(Cos(s / 180 * 3.141592) * 30) + 401
        For b = .5 To -.5 Step -.1
            Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
            Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
        Next b
    Next seconds
    For seconds = 45 To 60 Step 2
        s = (60 - seconds) * 6 + 180
        x = Int(Sin(s / 180 * 3.141592) * 30) + weeds
        y = Int(Cos(s / 180 * 3.141592) * 30) + 401
        For b = .5 To -.5 Step -.1
            Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
            Line (weeds + b, 401)-(x + b, y), _RGB32(61, 255, 0)
        Next b
    Next seconds
Next weeds

weeds = 725

For seconds = 0 To 15 Step 4
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + weeds
    y = Int(Cos(s / 180 * 3.141592) * 60) + 401
    For b = .7 To -.7 Step -.1
        Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
        Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
    Next b
Next seconds
For seconds = 45 To 60 Step 4
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + weeds
    y = Int(Cos(s / 180 * 3.141592) * 60) + 401
    For b = .7 To -.7 Step -.1
        Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
        Line (weeds + b, 401)-(x + b, y), _RGB32(61, 216, 127)
    Next b
Next seconds

For seconds = 0 To 15 Step 2
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 30) + weeds
    y = Int(Cos(s / 180 * 3.141592) * 30) + 401
    For b = .5 To -.5 Step -.1
        Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
        Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
    Next b
Next seconds
For seconds = 45 To 60 Step 2
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 30) + weeds
    y = Int(Cos(s / 180 * 3.141592) * 30) + 401
    For b = .5 To -.5 Step -.1
        Line (weeds + b, 401)-(x + b, y), _RGB32(0, 255, 0)
        Line (weeds + b, 401)-(x + b, y), _RGB32(61, 255, 0)
    Next b
Next seconds



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)

'a little beefier carpentry - from OldMoses
For beam% = 0 To 19
    If beam% Mod 2 = 0 Then c~& = &HFF964B00 Else c~& = &HFF7F7F7F
    Line (600 - beam%, 400)-(600 - beam%, 100 + beam%), c~& 'vertical post
    Line (600 - beam%, 100 + beam%)-(400 + beam, 100 + beam%), c~& 'horizontal post
Next beam%
Line (550, 400)-(630, 375), _RGB32(255, 255, 255), BF

randword:
word$ = words$(Int(Rnd * w) + 1)
l = Len(word$)
If l > 12 Or l < 2 Then GoTo randword:

For lines = 203 To 203 + ((l - 1) * 50) Step 50
    Line (lines - 5, 505)-(lines + 15, 475), _RGB32(255, 255, 255), BF
    Line (lines, 500)-(lines + 10, 500), _RGB32(0, 0, 0)
Next lines

Line (40, 440)-(160, 505), _RGB32(255, 255, 255), BF

For ll = 1 To l
    letter$(ll) = Mid$(word$, ll, 1)
    If Asc(letter$(ll)) < 97 Or Asc(letter$(ll)) > 122 Then GoTo start:
    letter2$(ll) = letter$(ll)
Next ll
letter = 0: oldletter = 0
mistake = 0: t = 1
Color _RGB32(0, 0, 0), _RGB32(255, 255, 255)
go:

g = 0
Do
    _Limit 20
    a$ = InKey$
    If a$ <> "" Then GoTo continue:
Loop

continue:
a$ = LCase$(a$)
If a$ = Chr$(27) Then End
t = t + 1
oldletter = letter
For ll = 1 To l
    If a$ = letter$(ll) Then
        If g < 1 Then letter$(ll) = ""
        g = 1
        letter = letter + 1
        _PrintString (205 + (ll - 1) * 50, 480), a$
        For snd = 200 To 700 Step 100
            Sound snd, .5
        Next snd
        If letter = l Then GoTo won:
    End If
Next ll


If oldletter <> letter Then GoTo go:

mistake = mistake + 1

'Head
If mistake = 1 Then
    For sz = .25 To 20 Step .25
        Circle (400, 200), sz, _RGB32(194, 127, 127)
    Next sz
    _PrintString (50, 450), a$
    Sound 200, .5
    Sound 600, .5
End If

'Body
If mistake = 2 Then
    Line (395, 220)-(405, 240), _RGB32(194, 127, 127), BF
    For sz = .25 To 40 Step .25
        Circle (400, 270), sz, _RGB32(61, 216, 127), , , 1.85
    Next sz
    _PrintString (75, 450), a$
    Sound 200, .5
    Sound 600, .5
End If

'Left Arm
If mistake = 3 Then
    seconds = 55
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + 390
    y = Int(Cos(s / 180 * 3.141592) * 60) + 240
    For b = 5 To -5 Step -.1
        Line (390 + b, 240)-(x + b, y), _RGB32(61, 216, 127)
        Line (390 + b, 240)-(x + b, y), _RGB32(61, 216, 127)
    Next b
    For sz = .25 To 6.5 Step .25
        Circle (x + 1, y), sz, _RGB32(194, 127, 127), 2 * _Pi, _Pi
    Next sz
    _PrintString (100, 450), a$
    Sound 200, .5
    Sound 600, .5
End If

'Right Arm
If mistake = 4 Then
    seconds = 5
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + 410
    y = Int(Cos(s / 180 * 3.141592) * 60) + 240
    For b = 5 To -5 Step -.1
        Line (410 + b, 240)-(x + b, y), _RGB32(61, 216, 127)
        Line (410 + b, 240)-(x + b, y), _RGB32(61, 216, 127)
    Next b
    For sz = .25 To 6.5 Step .25
        Circle (x - 1, y), sz, _RGB32(194, 127, 127), 2 * _Pi, _Pi
    Next sz
    _PrintString (125, 450), a$
    Sound 200, .5
    Sound 600, .5
End If

'Left Leg
If mistake = 5 Then
    seconds = 35
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + 390
    y = Int(Cos(s / 180 * 3.141592) * 60) + 290
    For b = 5 To -5 Step -.1
        Line (390 + b, 290)-(x + b, y), _RGB32(61, 216, 127)
        Line (390 + b, 290)-(x + b, y), _RGB32(61, 216, 127)
    Next b
    For sz = .25 To 6.5 Step .25
        Circle (x + 1, y), sz, _RGB32(194, 127, 127), _Pi, 2 * _Pi
    Next sz
    _PrintString (150, 450), a$
    Sound 200, .5
    Sound 600, .5
End If

'Right Leg
If mistake = 6 Then
    seconds = 25
    s = (60 - seconds) * 6 + 180
    x = Int(Sin(s / 180 * 3.141592) * 60) + 410
    y = Int(Cos(s / 180 * 3.141592) * 60) + 290
    For b = 5 To -5 Step -.1
        Line (410 + b, 290)-(x + b, y), _RGB32(61, 216, 127)
        Line (410 + b, 290)-(x + b, y), _RGB32(61, 216, 127)
    Next b
    For sz = .25 To 6.5 Step .25
        Circle (x, y), sz, _RGB32(194, 127, 127), _Pi, 2 * _Pi
    Next sz
    _PrintString (50, 475), a$
    Sound 200, .5
    Sound 600, .5
End If

'Eyes
If mistake = 7 Then
    For sz = .25 To 3 Step .25
        Circle (390, 190), sz, _RGB32(255, 255, 255)
        Circle (410, 190), sz, _RGB32(255, 255, 255)
    Next sz
    For sz = .25 To 1.75 Step .25
        Circle (390, 190), sz, _RGB32(0, 161, 255)
        Circle (410, 190), sz, _RGB32(0, 161, 255)
    Next sz
    For sz = .25 To 1 Step .25
        Circle (390, 190), sz, _RGB32(0, 0, 0)
        Circle (410, 190), sz, _RGB32(0, 0, 0)
    Next sz
    _PrintString (75, 475), a$
    Sound 200, .5
    Sound 600, .5
End If

'Nose
If mistake = 8 Then
    For sz = .25 To 3 Step .25
        Circle (400, 200), sz, _RGB32(78)
    Next sz
    _PrintString (100, 475), a$
    Sound 200, .5
    Sound 600, .5
End If

'Mouth
If mistake = 9 Then
    For sz = .25 To 8 Step .25
        Circle (400, 212), sz, _RGB32(0, 0, 0), , , .5
    Next sz
    _PrintString (125, 475), a$
    For snd = 700 To 100 Step -50
        Sound snd, .5
    Next snd
    For ll = 1 To l
        _PrintString (205 + (ll - 1) * 50, 480), letter2$(ll)
    Next ll
    _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! "
For s = 1 To 2
    For snd = 100 To 800 Step 100
        Sound snd, .5
    Next snd
Next s
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

'Almost all of the following words were found here: https://www.ef.edu/english-resources/english-vocabulary/top-1000-words/
ManyWords:
Data ability,able,about,above,accept,according,account,across,act,action
Data activity,actually,add,address,administration,admit,adult,affect,after,again
Data against,age,agency,agent,ago,agree,agreement,ahead,air,all
Data allow,almost,alone,along,already,also,although,always,among,amount
Data analysis,and,animal,another,answer,any,anyone,anything,appear,apply
Data approach,area,argue,arm,around,arrive,art,article,artist,as
Data ask,assume,at,attack,attention,attorney,audience,author,authority,available
Data avoid,away,baby,back,bad,bag,ball,bank,bar,base
Data be,bear,beat,beautiful,because,become,bed,before,begin,behavior
Data behind,believe,benefit,best,better,between,beyond,big,bill,billion
Data bit,black,blood,blue,board,body,book,born,both,box
Data boy,break,bring,brother,budget,build,building,business,but,buy
Data by,call,camera,campaign,can,cancer,candidate,capital,car,card
Data care,career,carry,case,cat,catch,cause,cell,center,central
Data century,certain,certainly,chair,challenge,chance,change,character,charge,check
Data child,choice,choose,church,citizen,city,civil,claim,class,clear
Data clearly,close,coach,cold,collection,college,color,come,commercial,common
Data community,company,compare,computer,concern,condition,conference,consider,consumer,contain
Data continue,control,cost,could,country,couple,course,court,cover,cow
Data create,crime,cultural,culture,cup,current,customer,cut,dark,data
Data daughter,day,dead,deal,death,debate,decade,decide,decision,deep
Data defense,degree,democratic,describe,design,despite,detail,determine,develop,development
Data die,difference,different,difficult,dinner,dinosaur,direction,director,discover,discuss
Data discussion,disease,do,doctor,dog,door,down,draw,dream,drive
Data drop,drug,during,each,early,east,easy,eat,economic,economy
Data edge,education,effect,effort,eight,either,election,elephant,else,employee
Data end,energy,enjoy,enough,enter,entire,environment,especially,establish,even
Data evening,event,ever,every,everybody,everyone,everything,evidence,exactly,example
Data executive,exist,expect,experience,expert,explain,eye,face,fact,factor
Data fail,fall,family,far,fast,father,fear,federal,feel,feeling
Data few,field,fight,figure,fill,film,final,finally,financial,find
Data fine,finger,finish,fire,firm,first,fish,five,floor,fly
Data focus,follow,food,foot,for,force,foreign,forget,form,former
Data forward,four,free,friend,from,front,full,fund,future,game
Data garden,gas,general,generation,get,girl,give,glass,go,goal
Data good,government,great,green,ground,group,grow,growth,guess,gun
Data guy,hair,half,hand,hang,happen,happy,hard,have,he
Data head,health,hear,heart,heat,heavy,help,her,here,herself
Data high,him,himself,his,history,hit,hold,home,hope,horse
Data hospital,hot,hotel,hour,house,how,however,huge,human,hundred
Data husband,idea,identify,if,image,imagine,impact,important,improve,in
Data include,including,increase,indeed,indicate,individual,industry,information,inside,instead
Data institution,interest,interesting,interview,into,investment,involve,issue,it,item
Data its,itself,job,join,just,keep,key,kid,kill,kind
Data kitchen,know,knowledge,land,language,large,last,late,later,laugh
Data law,lawyer,lay,lead,leader,learn,least,leave,left,leg
Data legal,less,let,letter,level,lie,life,light,like,likely
Data line,list,listen,little,live,local,long,look,lose,loss
Data lot,love,low,machine,magazine,main,maintain,major,majority,make
Data man,manage,management,manager,many,market,marriage,material,matter,may
Data maybe,me,mean,measure,meat,media,medical,meet,meeting,member
Data memory,mention,message,method,middle,might,military,million,mind,minute
Data miss,mission,model,modern,moment,money,month,more,morning,most
Data mother,mouth,move,movement,movie,much,music,must,my,myself
Data name,nation,national,natural,nature,near,nearly,necessary,need,network
Data never,new,news,newspaper,next,nice,night,no,none,nor
Data north,not,note,nothing,notice,now,number,occur,of,off
Data offer,office,officer,official,often,oh,oil,ok,old,on
Data once,one,only,onto,open,operation,opportunity,option,or,order
Data organization,other,others,our,out,outside,over,own,owner,page
Data pain,painting,paper,parent,part,participant,particular,particularly,partner,party
Data pass,past,patient,pattern,pay,peace,people,per,perform,performance
Data perhaps,period,person,personal,phone,physical,pick,picture,piece,pig
Data place,plan,plant,play,player,plot,point,police,policy,political
Data politics,poor,popular,population,position,positive,possible,power,practice,prepare
Data present,president,pressure,pretty,prevent,price,private,probably,problem,process
Data produce,product,production,professional,professor,program,project,property,protect,prove
Data provide,public,pull,purpose,push,put,quality,question,quickly,quite
Data race,radio,raise,range,rate,rather,reach,read,ready,real
Data reality,realize,really,reason,receive,recent,recently,recognize,record,red
Data reduce,reflect,region,relate,relationship,religious,remain,remember,remove,report
Data represent,require,research,resource,respond,response,rest,result,return,reveal
Data rich,right,rise,risk,road,rock,role,room,rule,run
Data safe,same,save,say,scene,school,science,scientist,score,sea
Data season,seat,second,section,security,see,seek,seem,sell,send
Data senior,sense,series,serious,serve,service,set,seven,several,sex
Data sexual,shake,share,she,shoot,short,shot,should,shoulder,show
Data side,sign,significant,similar,simple,simply,since,sing,single,sister
Data sit,site,situation,six,size,skill,skin,small,smile,so
Data social,society,soldier,some,somebody,someone,something,sometimes,son,song
Data soon,sort,sound,source,south,southern,space,speak,special,specific
Data speech,spend,sport,spring,staff,stage,stand,standard,star,start
Data state,statement,station,stay,step,still,stock,stop,store,story
Data strategy,street,strong,structure,student,study,stuff,style,subject,success
Data successful,such,suddenly,suffer,suggest,summer,support,sure,surface,system
Data table,take,talk,task,tax,teach,teacher,team,technology,telephone
Data television,tell,ten,tend,term,test,than,thank,that,the
Data their,them,themselves,then,theory,there,these,they,thing,think
Data third,this,those,though,thought,thousand,threat,three,through,throughout
Data throw,thus,time,to,today,together,tonight,too,top,total
Data tough,toward,town,trade,traditional,training,travel,treat,treatment,tree
Data trial,trip,trouble,truck,true,truth,try,turn,two,type
Data under,understand,unit,until,up,upon,us,use,usually,value
Data various,very,victim,view,violence,visit,voice,vote,wait,walk
Data wall,want,war,watch,water,way,we,weapon,wear,week
Data weight,well,west,western,what,whatever,when,where,whether,which
Data while,white,who,whole,whom,whose,why,wide,wife,will
Data win,wind,window,wish,with,within,without,woman,wonder,word
Data work,worker,world,worry,would,write,writer,wrong,xylophone,yard
Data yeah,year,yes,yet,you,young,your,yourself,zebra,zoo,monotonous
Reply
#18
Noice !!!   Big Grin
Of all the places on Earth, and all the planets in the Universe, I'd rather live here (Perth, W.A.) Big Grin
Please visit my Website at: http://oldendayskids.blogspot.com/
Reply




Users browsing this thread: 2 Guest(s)