8-Bit Software Online Conversion

Spelling - Listing

10DEFFNS="LPenSp" 20MODE7:VDU23;8202;0;0;0; 30W%=10:REM WORD TO COPY 40G%=14:REM WORD SO FAR 50S%=18:REM ALPHABET 60H%=5:REM LINE SO FAR 70B%=96:*FX202 48 80J%=0 90K%=50:REM MAXIMUM AND INITIAL NUMBE R OF WORDS 100T%=0 110Q%=0 120R%=0 130DIM E$(K%) 140FORL%=1TOK% 150E$(L%)="*" 160NEXT 170PROCsetup 180ONERROR:VDU0 190PROCtitles 200REPEAT 210REPEAT 220*FX21 230A$=GET$ 240IFA$="1"PROCInfo:PROCtitles 250IFA$="4"PROCcreate:PROCtitles 260IFA$="5"PROCoptions:PROCtitles 270IFA$="6":OSCLI"FX202 32":END 280UNTILINSTR("23",A$) 290D%=VAL(A$) 300IFD%=2 OR D%=3 PROCmain 310UNTILFALSE 320DEFPROCtitles 330CLS 340PRINT 350PROCc("       370PRINT 380PROCc(" By C.J.Richardson.") 390PRINT 400PROCc(" Please Enter Your Choice 1- 6") 410PRINT''" 1. Info. " 420PRINT" 2. Start using DATA in pro gram. " 430PRINT" 3. Start using file from d isc. " 440PRINT" 4. Edit/Add/View words on disc. " 450PRINT" 5. Options. " 460PRINT" 6. End. " 470A$="" 480ENDPROC 490DEFPROCoptions 500REPEAT 510CLS 520PRINT 530PROCc("   550PRINT 560PROCc(" Please Enter Your Choice 1- 8") 570PRINT''TAB(5)" 1. Timing "; 580IFT%=0 PRINT"off." ELSE IF T%=1 PRI NT"on." 590PRINTTAB(5)" 2. Prompt stays "; 600IFQ%<>0 PRINT"for ";STR$(Q%);" sec" 610PRINTTAB(5)" 3. "; 620IFR%=0 PRINT"Normal"; 630IFR%=1 PRINT"Scrambled"; 640PRINT" prompt." 650PRINTTAB(5)" 4. Force UPPER case." 660PRINTTAB(5)" 5. Force lower case." 670PRINTTAB(5)" 6. Set light pen offse t." 680PRINTTAB(5)" 7. Set number of words used." 690PRINTTAB(5)" 8. Return to main menu ." 700REPEAT 710*FX21 720A$=GET$ 730UNTILINSTR("12345678",A$) 740IFA$="1"T%=1 EOR T% 750IFA$="2"PRINTTAB(0,15);" Enter dela y in seconds before prompt"'" disappears ";:INPUT" ";Q% 760IFA$="3"R%=1 EOR R% 770IFA$="4"B%=64 780IFA$="5"B%=96 790IFA$="6"PRINT''" Enter light pen of fset (-1 0 1)":INPUT" ";J% 800IFA$="7"REPEAT:PRINT''" Enter numbe r of words used."'" Presently ";STR$(K%- 1);". Maximum 49.":INPUT" ";K%:K%=K%+1:U NTILK%>1 AND K%<51:E$(K%)="*" 810UNTILA$="8" 820ENDPROC 830DEFPROCc(A$) 840PRINTTAB(20-LEN(A$)/2);A$ 850ENDPROC 860DEFPROCresetscreen 870VDU12,30:FORL%=1TO23:VDU135,157,133 ,10,13:NEXT:VDU135,157,133 880ENDPROC 890DEFPROCscreen 900PROCresetscreen 910VDU31,7,S%,ASC"   930VDUL%,10,8,L%,11,9 940NEXT 950VDU31,7,S%+2,ASC"   960FORL%=B%+14 TO B%+26 970VDUL%,10,8,L%,11,9 980NEXT 990ENDPROC 1000DEFPROCloadin(B$) 1010REPEAT 1020CLS 1030*. 1040PRINT 1050PROCc(B$) 1060INPUT'" "F$ 1070UNTILF$<>"" 1080F%=OPENIN(F$) 1090L%=0 1100REPEAT 1110L%=L%+1 1120INPUT#F%,E$(L%) 1130UNTILE$(L%)="*" 1140CLOSE#F% 1150E$(K%)="*" 1160ENDPROC 1170DEFPROCcreate 1180REPEAT 1190CLS 1200PROCc("     1220PRINT 1230PROCc(" Please Enter Your Choice 1- 7") 1240PRINT'TAB(5)" 1. Start new word fil e." 1250PRINTTAB(5)" 2. Load word file from disc." 1260PRINTTAB(5)" 3. Load word file from DATA." 1270PRINTTAB(5)" 4. Examine word file i n memory." 1280PRINTTAB(5)" 5. Alter word in memor y." 1290PRINTTAB(5)" 6. Save word file in m emory." 1300PRINTTAB(5)" 7. Return to main menu ."' 1310REPEAT 1320A$=GET$ 1330UNTILINSTR("1234567",A$) 1340IFA$="1"PROCent 1350IFA$="2"PROCloadin(" Enter file n ame to load: ") 1360IFA$="3"PROCgetdata 1370IFA$="4"PROCexamine 1380IFA$="5"PROCalter 1390IFA$="6"PROCsave 1400UNTIL A$="7" 1410ENDPROC 1420DEFPROCalter 1430PRINT'' 1440PROCc(" Enter word number to alte r: ") 1450REPEAT 1460INPUT'" ";L% 1470UNTILL%>0 AND L%<K% 1480PRINT" Word "+STR$(L%)" :";" ";E$(L %) 1490PROCgetword 1500ENDPROC 1510DEFPROCexamine 1520CLS 1530VDU14 1540PROCc(" Press SHIFT to continue. ") 1550PRINT 1560FORL%=1 TO K% 1570PRINT" "STR$(L%);". ";E$(L%) 1580NEXT 1590PRINT' 1600PROCc(" Press a key for menu. " ) 1610*FX21 1620VDU15 1630REPEATUNTILGET 1640ENDPROC 1650DEFPROCent 1660A$=" You may enter up to "+STR$(K%- 1)+" words." 1670PRINT 1680PROCc(A$) 1690PROCc(" Enter the word then press R ETURN") 1700PROCc(" Type only letters A-Z and a -z.") 1710A$=" To finish before "+STR$(K%-1)+ " words, enter a *" 1720PROCc(A$) 1730PRINT 1740L%=1 1750REPEAT 1760PROCgetword 1770UNTILE$(L%-1)="*" OR L%=K% 1780PROCsave 1790ENDPROC 1800DEFPROCgetword 1810REPEAT 1820PRINT" Enter word ";STR$(L%);" "; 1830INPUTLINEA$ 1840M%=0 1850FORI%=1TOLENA$ 1860N%=ASC(MID$(A$,I%,1)) 1870IF N%<65 OR N%>122 OR N%>90 AND N%< 97 M%=1 1880IF A$="*" M%=0 1890NEXT 1900UNTIL M%=0 1910E$(L%)=A$:L%=L%+1 1920ENDPROC 1930DEFPROCsave 1940L%=0 1950E$(K%)="*" 1960REPEAT 1970CLS 1980*. 1990PRINT 2000PROCc(" Enter File Name to Save b y: ") 2010INPUT'" ";F$ 2020UNTILF$<>"" 2030F%=OPENOUT(F$) 2040FORL%=1TOK% 2050PRINT#F%,E$(L%) 2060NEXT 2070CLOSE#F% 2080ENDPROC 2090DEFPROCmain 2100IFD%=3 PROCloadin(" Enter file na me to load: ") 2110IFD%=2 PROCgetdata 2120REPEAT 2130F%=1 2140PROCscreen 2150X$="" 2160TIME=0 2170REPEAT 2180W$="" 2190N$=E$(F%) 2200F%=F%+1 2210IF N$="*":PROCfinished ELSE PROCano ther 2220UNTIL N$="*" 2230UNTILFALSE 2240ENDPROC 2250DEFPROCgetdata 2260REPEAT 2270CLS 2280PRINT''" Select block of words (1 to 30): " 2290INPUT'" ";V% 2300UNTILV%>0 AND V%<31 2310L%=V% 2320RESTORE 2330IF L%=1 PROCreadin:ENDPROC 2340REPEAT 2350READA$ 2360IFA$="*":L%=L%-1 2370UNTILL%=1 2380PROCreadin 2390ENDPROC 2400DEFPROCreadin 2410FORL%=1TOK% 2420READ E$(L%) 2430NEXT 2440E$(K%)="*" 2450ENDPROC 2460DEFPROCanother 2470FORL%=1TOLEN(N$) 2480IF B%=64 W$=W$+(CHR$(ASC(MID$(N$,L% ,1))AND &DF)) 2490IF B%=96 W$=W$+(CHR$(ASC(MID$(N$,L% ,1))OR B%)) 2500NEXT 2510G$="" 2520Y$=W$ 2530IF R%=1 PROCscramble 2540PRINTTAB(20-(LEN(W$)/2),W%);"   $ 2560IF Q%<>0:Z%=TIME:REPEATUNTILTIME=Z% +Q%*100:PRINTTAB(5,W%)SPC(30):PRINTTAB(5 ,W%+1)SPC(30) 2570REPEAT 2580C%=0 2590IF B%=64:*FX202 32 2600IF B%=96:*FX202 48 2610PROCGetPos 2620PROCCalcLetter 2630IF C%=ASC(MID$(W$,LEN(G$)+1,1)) G$= G$+CHR$C%:SOUND1,-12,70,1:SOUND1,0,1,1 2640PRINTTAB(20-(LEN(G$)/2),G%)"   2660UNTILG$=W$ 2670PROCWellDone 2680X$=X$+" "+W$ 2690X$=RIGHT$(X$,35) 2700X$=MID$(X$,INSTR(X$," "),LEN(X$)) 2710PRINTTAB(3,H%);"   2720ENDPROC 2730DEFPROCscramble 2740IF LEN(W$)<>1 REPEAT:Y$=W$ 2750V$="" 2760FORL%=1TOLEN(Y$) 2770REPEAT 2780I%=RND(LEN(Y$)) 2790T$=MID$(Y$,I%,1) 2800UNTILT$<>" " 2810V$=V$+MID$(Y$,I%,1) 2820Y$=LEFT$(Y$,I%-1)+" "+MID$(Y$,I%+1) 2830NEXT 2840Y$=V$ 2850IF LEN(W$)<>1 UNTILY$<>W$ 2860ENDPROC 2870DEFPROCWellDone 2880SOUND1,-12,70,1:SOUND1,0,1,1 2890PRINTTAB(5,W%)SPC(30) 2900PRINTTAB(5,W%+1)SPC(30) 2910PRINTTAB(5,G%)SPC(30) 2920PRINTTAB(5,G%+1)SPC(30) 2930ENDPROC 2940DEFPROCGetPos 2950A%=!&74 2960A%=A%+J% 2970X%=(A%-8)MOD40 2980Y%=A%DIV40-255 2990ENDPROC 3000DEFPROCCalcLetter 3010IF INKEY(0)=ASC(MID$(W$,LEN(G$)+1,1 )):C%=ASC(MID$(W$,LEN(G$)+1,1)):OSCLI"FX 21":ENDPROC 3020IF X%<0 OR Y%<0 ENDPROC 3030IF Y%=S% OR Y%=S%+1 C%=(X%-5)/2+B%: ENDPROC 3040IF Y%=S%+4 OR Y%=S%+5 C%=(X%-5)/2+B %+13:ENDPROC 3050C%=32 3060ENDPROC 3070DEFPROCsetup 3080FORL%=0TO2 STEP 2 3090P%=&900 3100[:OPTL%:.i SEI 3110LDA#f MOD256:STA&206:LDA#f DIV256:S TA&207 3120LDA#&88:STA&FE4E:CLI:RTS 3130.f LDA&FC:PHA:TXA:PHA:TYA:PHA 3140LDA&FE4D:AND#&88:CMP#&88:BNEout 3150LDA&FE40:LDX#16:STX&FE00:INX 3160LDA&FE01:CMP&71:STA&71 3170BNEd:STX&FE00:LDA&FE01 3180TAY:SBC&70:CLC:ADC#1:BMIe 3190CMP#3:BCSe:STY&74:LDA&71 3200STA&75:JMPout 3210.d STX&FE00:LDY&FE01 3220.e STY&70:LDA#0:STA&74:STA&75 3230.out PLA:TAY:PLA:TAX:PLA:STA&FC:RTI :] 3240NEXT 3250!&70=0:!&74=0 3260*FX20,1 3270CALLi 3280VDU12 3290ENDPROC 3300DEFPROCInfo 3310CLS 3320PRINT"This program allows you to us e a light"'"pen or the keyboard to type in words."'"When using the light pen, po int at the"'"alphabet at the bottom of t he screen." 3330PRINT"The target word appears half way down"'"the screen. The word being bu ilt"'"appears below that. The last few w ords"'"appear at the top of the screen." '"There are options that" 3340PRINT"allow you to set the length o f time"'"this target word stays visible and"'"to scramble the target word." 3350PRINT"There is an option to time ho w long"'"it takes to work through a set of"'"words. There are 30 sets of 49 word s in"'"the program. There is an option t o load"'"a set of words from disc. There are" 3360PRINT"facilities to create, view an d edit"'"your own word files on disc."'" You can also force upper or lower case"' "throughout the program." 3370PRINT"It is possible to change the light pen"'"offset if the timing is diff erent." 3380PRINT'"PRESS A KEY TO CONTINUE."; 3390*FX21 3400REPEATUNTILGET 3410ENDPROC 3420DEFPROCfinished 3430PRINTTAB(15,1);"Well done!" 3440PRINTTAB(7,2);"Hold light pen here or press" 3450PRINTTAB(7,3);"the SPACE BAR to pla y again." 3460IF T%=1 PROCtime 3470REPEAT 3480PROCGetPos 3490UNTILY%=2 OR INKEY(0)=32 3500ENDPROC 3510DEFPROCtime 3520PRINTTAB(15,12);"That took you:" 3530U%=TIME/100 3540PRINTTAB(10,14);STR$(U%DIV60);" Min utes ";STR$(U%MOD60);" Seconds" 3550ENDPROC 10000DATAcar,jam,can,sad,hat,sat,man,ran ,rag,fat,wag,bad,mat,wax,van,leg,pet,get ,hen,pen,red,wet,met,let,jet,men,fed,set ,den,sit,hit,pig,dig,did,fix,kid,bit,fit ,lip,mix,hid,win,lid,fox,rob,log,lot,hot ,box,* 10010DATAcot,job,fog,hop,mop,pop,sob,hop ,rub,fun,but,cup,mum,bun,run,cub,cut,gum ,hug,hut,sun,sum,cry,fly,sky,shy,fry,try ,spy,my,dry,by,sty,sly,why,late,same,gam e,cake,make,cave,make,hate,page,take,wak e,gate,lane,wave,* 10020DATAfine,bite,hide,bike,kite,wide,w ife,ice,pie,pine,pipe,mice,size,line,hop e,nose,note,hole,rose,rope,joke,pole,toe ,hoe,vote,poke,woke,home,rude,use,tune,t ube,mule,huge,cube,duke,rule,cute,due,da d,bad,red,bin,nod,big,mud 10025DATAbed,did,bat,* 10030DATAcub,rob,dog,bib,add,odd,address ,middle,puddle,paddle,wedding,muddle,sad der,gladder,riddle,saddle,fiddle,off,off er,puff,puffin,toffee,coffee,office,offi cer,effect,effort,stiff,stuff,stuffy,cli ff,egg,buggy,bigger,hugged,mugger 10040DATAtrigger,wagged,leggings,biggest ,beggar,digger,doll,well,full,wall,ball, kill,fall,* 10050DATApull,fill,pillow,windmill,swall ow,balloon,shallow,kiss,miss,less,lesson ,mess,grass,cross,fuss,guess,message,cla ssroom,missile,missing,loss,quick,quack, quilt,quite,quiet,quarter,queen,question ,quickly,quality,quarrel,quantity 10060DATAthat,then,this,them,they,mother ,brother,these,those,bother,leather,fath er,feather,breathe,moth,cloth,* 10070DATAtooth,bath,path,think,thank,thi ng,mouth,south,truth,thief,birthday,thir ty,chin,chips,chop,much,child,chick,chai n,cheer,cheese,cheeky,beach,chilly,cherr y,chimney,ship,shop,shed,wash,rush,wish, shot,shell,crash,brush,shout 10080DATAsheep,show,shower,ring,sing,ran g,song,lung,long,longer,thing,sting,* 10090DATAbring,cling,singer,strong,belon g,back,pick,tick,sick,lick,kick,suck,stu ck,clock,black,ticket,jacket,packet,stoc king,guess,guard,guide,guitar,guest,tong ue,guilty,guarantee,league,knee,knife,kn ow,knot,knit,knock,kneel,knew 10100DATAknob,knitting,knight,knowledge, unknown,knives,walk,chalk,talk,stalk,yol k,folk,walking,* 10110DATAlamb,dumb,thumb,bomb,comb,climb ,crumb,limb,debt,doubt,bomber,climber,ph one,photo,elephant,phantom,dolphin,alpha bet,telephone,graph,photograph,geography ,listen,fasten,castle,whistle,thistle,fa stener,listening,when,which,what 10120DATAwhite,why,whale,while,wheel,whi p,whisper,whistle,whisker,wheat,write,wr ist,writer,wrong,wrap,wren,wreath,* 10130DATAwriting,wreck,wrapper,wriggle,w restling,edge,badge,badger,bridge,fidget ,hedge,judge,fudge,fridge,midget,knowled ge,catch,patch,watch,match,matchbox,pitc h,hutch,ditch,witch,watching,stitch,batc h,snatch,stretch,old,hold,held,gold 10140DATAgoldfish,sold,cold,told,child,g olden,bold,fold,children,shoulder,lamp,d amp,imp,camp,jump,* 10150DATAjumper,bump,lump,pump,pumpkin,s imple,company,computer,mumps,hand,land,s and,band,bend,pond,wind,pound,sandwich,w indow,bandage,mending,defend,standard,pi nk,bunk,tank,sink,wink,sunk,bank,drink,t hink,blink,shrink,thanks,tanker 10160DATAtwinkle,bent,went,tent,sent,hun t,dent,dentist,pants,wanted,haunted,fron t,grunt,* 10170DATAlantern,event,desk,ask,mask,ris k,rusk,asked,tusk,task,risky,frisky,bask et,whisker,last,test,fast,post,postman,c ost,west,mister,master,mistake,poster,fa ster,toast,sister,pinch,punch,munch,bunc h,branch,lunch,bench,ranch,crunch 10180DATAblack,blob,bless,block,blow,bli nk,blunt,blanket,bloom,blackboard,blosso m,blood,* 10190DATAblue,blindfold,clap,class,clock ,cloth,clothes,club,cliff,clay,climb,clo wn,cloud,claw,classroom,clothing,flat,fl y,flag,flame,flower,flash,flap,floor,flo ck,flesh,flood,cornflakes,butterfly,flig ht,glad,gleam,glass,glasses 10200DATAglove,glue,glow,glowing,glimpse ,gleaming,glide,glory,globe,plate,plus,p lay,planet,plant,place,* 10210DATAplastic,plan,platform,plum,plea se,plenty,playground,plaster,bring,brick ,brush,brave,brown,brownie,brother,brook ,bread,bridge,breath,branch,breakfast,br ain,crab,crack,cry,cross,crossing,crash, crown,cracker,crayon,cream,crime 10220DATAcrew,crowd,cricket,dry,drum,dro p,drive,driver,drip,drag,dragon,dress,dr ink,drain,drawer,drawing,* 10230DATAdream,frog,from,frost,front,fre sh,friend,fry,frame,freezer,fright,frigh tened,freedom,fruit,friendship,grin,gree n,grape,grass,granny,grandad,grow,growl, great,gravy,greengrocer,ground,group,gra pe,prize,prince,princess,problem 10240DATApretty,press,prison,price,produ ce,protect,promise,proper,present,projec t,trip,trick,truck,trap,tractor,train,* 10250DATAtree,treat,track,traffic,tramp, treasure,truthful,troublesome,scale,scar ,scarf,scare,scared,score,scout,scooter, escape,hopscotch,scales,telescope,skip,s kin,sky,skate,ski,skeleton,skirt,skating ,skill,skipping,skid,skimmed,slow 10260DATAslip,sleep,asleep,sledge,slide, slippers,slice,slowly,slave,slippery,sle pt,sleeve,smile,smell,smoke,smooth,* 10270DATAsmart,smack,small,smash,smiling ,smelly,snip,snap,snug,snail,snake,snow, snowman,snowball,snowflake,snatch,spin,s pade,spite,spider,spell,spelling,space,s parrow,spark,spotted,speed,spear,sport,s poon,stop,stone,step,stick,star 10280DATAstamp,story,stairs,stable,start ,stocking,stool,study,storm,swim,swimmin g,swam,swing,swop,* 10290DATAsweet,sweep,switch,swear,sweat, sweater,swan,swallow,twins,twig,twist,tw inkle,twenty,between,twelve,twice,scrap, scrape,scratch,scream,screen,screw,scrub ,scribble,describe,scrambled,string,stro ng,street,stroke,strip,stripe,strange 10300DATAstrike,stranger,stream,straw,st rap,strawberry,stretch,three,thread,thro at,throne,throw,thrown,thrush,threaten,a id,* 10310DATAwait,aim,sail,nail,rain,paint,p ainting,faith,gaining,raining,raise,rais in,sailor,mountain,pause,cause,because,a unt,haunt,author,autumn,audience,sauce,s aucer,sausage,cauliflower,automobile,hau nted,saw,paw,raw,crawl,yawn,draw 10320DATAdrawer,lawn,jaw,hawk,dawn,law,l awyer,drawing,hay,lay,day,gay,say,play,c lay,* 10330DATAtray,crayon,saying,player,payme nt,railway,mayor,meal,seal,team,steam,be ach,heaven,weapon,wealthy,meadow,leather ,beast,heater,peanut,season,tree,need,ne edle,queen,feet,feeling,speed,bleed,chee k,cheese,meeting,seesaw,speech,teeth 10340DATAreindeer,receive,seize,ceiling, deceive,deceit,conceited,received,few,fl ew,grew,crew,stew,drew,* 10350DATAnewt,news,newspaper,jewel,screw ,threw,they,obey,eye,key,monkey,honey,mo ney,turkey,chimney,valley,jersey,journey ,hockey,donkey,field,friend,chief,believ e,mischief,thief,niece,friendly,friendsh ip,handkerchief,oak,boat,road,coat 10360DATAsoap,coach,toad,broad,coal,coas t,float,roast,oats,toadstool,oil,boil,no ise,noisy,soil,* 10370DATApoint,poison,avoid,toilet,voice ,boiling,pointed,food,fool,school,book,l ook,blood,spoon,bloom,brook,scooter,toot h,toothbrush,wooden,moonlight,about,roun d,pound,soup,group,trouble,couple,shout, shoulder,country,cousin,count 10380DATAhousehold,trousers,show,blow,th row,brown,cowboy,clown,power,brownie,cro wd,crown,growth,knowledge,mower,crow,* 10390DATAtoy,boy,joy,enjoy,annoy,royal,d estroy,oyster,cowboy,enjoyment,dark,park ,mark,garden,march,garage,parade,argumen t,darling,darkness,market,parcel,artist, harvest,her,term,person,jersey,perfume,h erd,very,period,overalls,mineral 10400DATAservice,servant,several,perfect ,girl,bird,birth,first,third,stir,skirt, shirt,dirty,thirty,thirsty,* 10410DATAthirteen,birthday,blackbird,for k,short,corn,corner,morning,sports,fort, fortune,horse,border,effort,torch,force, orchard,word,work,worm,world,worth,worke r,password,worthless,worse,worst,burn,tu rn,turnip,nurse,purse,church,turkey 10420DATAturtle,murder,purpose,purchase, surprise,surface,surrender,fair,fairy,ch air,pair,stairs,upstairs,dairy,downstair s,* 10430DATAunfair,hairy,care,scare,caretak er,rare,dare,spare,share,careful,nightma re,compare,beware,software,ear,fear,clea r,appear,near,nearly,tear,rear,nearby,di sappear,beard,pearl,early,learn,earth,se arch,heard,year,learning,hire,wire 10440DATAfire,fireman,fireworks,bonfire, admire,tired,retired,sore,store,snore,sc ore,more,wore,shore,* 10450DATAtore,swore,before,forehead,our, sour,hour,court,poured,your,journey,cour age,neighbour,fourteen,tourist,favour,fa vourite,neighbourhood,eight,weigh,neigh, neighbour,sleigh,weight,eighty,eighteen, neighbourhood,high,sigh,highway,right 10460DATAnight,sight,light,lightning,hig hest,nightmare,midnight,fright,bright,kn ight,plough,dough,though,rough,tough,cou gh,thought,bought,* 10470DATAbrought,doughnut,fought,althoug h,along,asleep,alive,alike,again,across, ashamed,about,around,apart,aboard,above, afraid,agree,before,behind,become,begin, beginning,below,behave,because,beside,be haviour,between,beneath,believe 10480DATAbeyond,beware,concrete,conditio n,contest,control,continent,consider,con quer,concert,conduct,conductor,container ,connect,continue,constable,desert,depar t,* 10490DATAdesign,defeat,delay,describe,de finite,defence,deserve,demand,department ,development,description,destroy,distanc e,district,discover,discovery,disease,di sagree,dismay,dismiss,dislike,disappear, disaster,disappointed,disgusting 10500DATAextra,exact,example,excuse,exci ting,experience,expect,expert,examinatio n,exchange,excitement,exercise,expeditio n,experiment,forbid,forgive,forget,forgo tten,forwards,fortune,forty,fortnight,fo rest,image,* 10510DATAimagine,imp,important,importanc e,immense,improve,impossible,imagination ,imitate,improvement,inside,insect,invis ible,interest,inform,invader,instead,ins tant,information,industry,influence,inst rument,index,perhaps,person,permit 10520DATApermission,perfect,period,perfu me,persuade,personal,present,prefer,prev ent,pretend,prepare,president,precious,p rescription,promise,problem,proper,prope rty,protect,protection,project,progress, professor,* 10530DATAprocess,procession,product,prot est,programme,referee,rely,reward,report ,record,result,return,religion,relief,re lative,relation,regard,refrigerator,resp ect,refreshments,unless,until,unfair,unp ack,undress,unhappy,untidy,undo 10540DATAuncover,unwell,uncertain,unfrie ndly,unknown,unpleasant,capable,lovable, comfortable,probable,suitable,unsuitable ,valuable,uncomfortable,reasonable,veget able,animal,final,hospital,sandal,signal ,* 10550DATAnatural,metal,petal,canal,gener al,several,sugar,collar,cellar,beggar,si milar,burglar,lunar,vinegar,shouted,mend ed,hated,tasted,counted,haunted,nodded,w icked,delighted,comforted,crowded,painte d,visited,wounded,cried,fried,sailed 10560DATAhugged,pulled,snowed,robbed,smi led,frowned,scrubbed,tired,worried,share d,married,hoped,hopped,licked,picked,suc ked,mashed,dropped,*