10 'ANAGRAMS
20 'Gavin Manning
30 'Amstrad Action June 88
40 MODE 1:INPUT"Anagram:",a$:a$=UPPER$(a$)
50 INPUT "Screen or printer:",s$
60 s$=UPPER$(s$)
70 IF LEFT$(s$,1)="S"THEN str%=0 ELSE IF LEFT$(s$,1)="P" THEN str%=8 ELSE 50
80 INPUT "Maximum word length:",maxl%
90 IF maxl%<1 THEN 80
100 INPUT "Minimum word length:",minl%
110 IF minl%>100 THEN PRINT "That's a bit silly !  ";:FOR d=1 TO 2000:NEXT d:PRINT "Oh well!":FOR d=1 TO 1000:NEXT d
120 'Check the minimum word length
130 IF minl%>maxl% THEN PRINT "That's too silly ! Having a greater minimum word length than maximum word   length !  Please re-enter both of them.":FOR d=1 TO 3000:NEXT d:GOTO 80
140 MODE 2:PRINT #str%,STRING$(80,"-"):PRINT#str%,a$:PRINT#str%:PRINT#str%,STRING$(80,"-"):PRINT#str%
150 WINDOW #0,1,80,7,25
160
65519 F
170 'Read the next word and check it is not the end of the data
180 READ w$
190 w$=UPPER$(w$)
200 IF w$="***THE END***"THEN 400
210 ''Save' the read-in word and the original anagram as they will both be corrupted by this routine
220 ow$=w$:oa$=a$
230 'Check length of read word
240 IF LEN(w$)>maxl% OR LEN(w$)<minl% OR LEN(w$)>LEN(a$) THEN 180
250 'Knock out any corresponding letters
260 FOR l%=1 TO LEN(w$)
270 z%=INSTR(a$,(MID$(w$,l%,1)))
280 IF z%<>0 THEN MID$(w$,l%,1)="*":MID$(a$,z%,1)="*"
290 NEXT l%
300 'If all the letters in the read-in word have been knocked out then you can get it from the 'anagram'.
310 s%=0
320 FOR l%=1 TO LEN(a$)
330 IF MID$(a$,l%,1)="*" THEN s%=s%+1
340 NEXT l%
350 'If you can get it from the 'anagram' then print it.
360 IF s%=LEN(w$) THEN PRINT #str%,ow$;".  ";
370 'Reset the anagram to it's original state
380 a$=oa$
390 GOTO 180              ::'Loop back
400 PRINT (TIME-t)/300:END::'Print the time taken
410 'The words to search through
420 DATA Hello,My,Name,Is,Gavin
430 DATA and,it,or,awe,ewe,them,he,she,us,we,i,you,a,mane,man,men,women,woman,gentle,gentleman,gentlemen,lady,ladies,lord,lord,penny,pennies,tea, eat,ate,water,club,clip,over,leaf,overleaf,tape,disc,base,bases,based,basic,basically,also,as,well
440 DATA on,in,top,with,for,who,which,where,when,to,from,skirt,trouser,skirts,dress,dresses,piano,siesta,mouse,tar,rat,art,pat,apt,tap,tape,tide,wave,rave,ride,tire,type,pot,option,king, queen,grand,hand,feet,foot,leg,head,hair,arm,hands,finger,glue,pens
450 DATA pencil,pencils,pen,sharp,knife,knives,wife,husband,band,drum,cymbal,greed,grit,hit,the,this,that,other,wreck,grope,desk,wood,drive,car,bike,house,paper,speaker,speak,print,date,day,week,month,year,manual,instruction,fire,place left,right,centre
460 DATA front,back,rear,behind,side,bottom,up,down,fast,slow,fat,tough,hide,hid,deftly,wedding,red,blue,yellow,is,was,has,been,come,television,vision,phone,telephone,write,ink, magazine,book,cupboard,bin,waste,size,small,big,large,enormous,tiny,huge
470 DATA curtain,window,glass,floor,ceiling,sweet,wheat,weak,bear,rib,rub,boar,bore,tor,rot,ore,lea,star,board,cup,saucer,coin,money,note,play,sleep,joy,stick,branch,rich,poor,poverty,strict,stricken,you,inn,inspire,spire,possible,spot,cafe,coffee,cake
480 DATA fruit,cherry,banana,apple,peach,ache,clean,vaccuum,hip,tip,lip,sip,dip,rip,nip,pip,job,equip,more,less,power,mop,bucket,space,sand,beach, sea,see,salt,land,earth,sky,dirt,filth,flannel,libel,po,bidet,toilet,seat,bench,bath,rug,mat,hearth,heart
490 DATA loop,soon,shine,moon,sun,son,daughter,father,mother,nan,grandad,uncle,aunt,great,time,old,new,ancient,antique,language,age,birth,death,beer, drink,food,stomach,brain,eye,nose,ear,nail,battery,cell,infantry,soldier,noose,rope,string,boss,worker
500 DATA loss,loose,lost,have,had,gone,shute,slide,radio,clock,badge,poster,post,reap,tramp,ream,onyx,cynical,oracle,text,finished,finish,start,end,beginning,word,cable,loop,pool,pond,lake,mountain,wrote,toe,ankle,click,country,county,region,prince,crown
65533 'It is best to keep the 'end-marker' data statement at the very end of the program as it is then very easy to add more words. If this statement is removed the program will not function properly.
65535 DATA ***THE END***