08-31-2022, 12:56 PM
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:
sha_na_na_na_na_na_na_na_na_na: