Microsoft Office Forums

Go Back   Microsoft Office Forums > >

Reply
 
Thread Tools Display Modes
  #1  
Old 01-11-2023, 09:06 PM
Alyb Alyb is offline Language detection Mac OS X Language detection Office 2016 for Mac
Novice
Language detection
 
Join Date: Jan 2023
Posts: 4
Alyb is on a distinguished road
Default Language detection

Since automatic language detection of paragraphs doesn’t always work reliable in Word for Mac, I would like to try out a macro that scans each paragraph of a German document for any of the most frequent English words:

The most commonly used words

I would remove those words that exist in German too (an, oh, etc.).

First I would assign the German language to the whole document. Then the macro should scan each paragraph for approximately 480 words. If they are found, the paragraph will be set to English, to enable correct spell checking.



Is it possible to do this at a reasonable speed, since many checks will be performed?

Perhaps it is better to use the opposite approach: test each word in a paragraph for presence in the list? Since paragraphs will rarely have 480 words, not even in legal German .

Since I'm not sure that a limited list of words will always be sufficient, in each and every context, it would be a good idea to have the words in an easy to edit list. So that the user can easily add words, e.g. for academic papers with a lot of quotations.

Any help will be greatly appreciated.

Last edited by Alyb; 01-12-2023 at 01:57 AM.
Reply With Quote
  #2  
Old 01-12-2023, 05:43 AM
macropod's Avatar
macropod macropod is offline Language detection Windows 10 Language detection Office 2016
Administrator
 
Join Date: Dec 2010
Location: Canberra, Australia
Posts: 21,962
macropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond repute
Default

For example:
Code:
Sub CheckGlobish()
Application.ScreenUpdating = False
Dim strWords As String, i As Long
strWords = strWords & "a,able,about,above,accept,accident,account,accuse,across,act,activist,actor,add,"
strWords = strWords & "administration,admit,adult,advertisement,advise,affect,afraid,after,again,against,"
strWords = strWords & "age,agency,aggression,ago,agree,agriculture,aid,aim,air,air,airplane,airport,album,"
strWords = strWords & "alive,all,ally,almost,alone,along,already,also,although,always,ammunition,among,"
strWords = strWords & "amount,anarchy,ancestor,ancient,and,anger,angle,angry,animal,anniversary,announce,"
strWords = strWords & "another,answer,any,apologize,appeal,appear,apple,appoint,approve,area,argue,arm,"
strWords = strWords & "army,around,arrest,arrive,art,artillery,as,ash,ask,assist,astronomy,at,atmosphere,"
strWords = strWords & "attach,attack,attempt,attend,attention,authority,automatic,automobile,autumn,avoid,"
strWords = strWords & "awake,award,away,baby,back,bad,bag,balance,ball,balloon,average,ballot,ban,bank,bar,"
strWords = strWords & "barrier,base,basket,battle,be,beat,beautiful,because,become,bed,before,begin,behind,"
strWords = strWords & "believe,bell,belong,below,bend,best,betray,better,between,big,bill,billion,biology,"
strWords = strWords & "bird,birth,bite,black,blade,blame,blanket,bleed,blind,block,blood,blow,blue,board,"
strWords = strWords & "boat,body,bomb,bone,book,border,born,borrow,both,bottle,bottom,box,boy,boycott,"
strWords = strWords & "brain,brake,branch,brass,brave,bread,break,breathe,brick,bridge,brief,bright,bring,"
strWords = strWords & "broadcast,brother,brown,brush,budget,build,building,bullet,burn,burst,bury,bus,"
strWords = strWords & "business,busy,but,butter,button,buy,by,cabinet,call,calm,camera,camp,campaign,can,"
strWords = strWords & "cancel,cancer,candidate,capital,capture,car,card,care,careful,carriage,carry,case,"
strWords = strWords & "cash,cat,catch,cause,celebrate,center,century,ceremony,certain,chain,chairman,"
strWords = strWords & "champion,chance,change,charge,chase,cheer,cheese,chemical,chemistry,chest,chief,"
strWords = strWords & "child,choose,church,circle,citizen,city,civilian,claim,clash,clean,clear,climate,"
strWords = strWords & "climb,clock,close,cloth,cloud,coal,coast,coat,coffee,cold,collar,collect,college,"
strWords = strWords & "colony,color,combine,come,comfort,command,comment,committee,common,communicate,"
strWords = strWords & "community,company,compare,compete,complete,complex,compromise,computer,concern,"
strWords = strWords & "condemn,condition,conference,confirm,congratulate,congress,connect,conservative,"
strWords = strWords & "consider,contain,continent,continue,control,convention,cook,cool,cooperate,copy,"
strWords = strWords & "cork,corn,correct,cost,cotton,count,country,court,cover,cow,crash,create,creature,"
strWords = strWords & "credit,crew,crime,criminal,crisis,criticize,crush,cry,culture,cup,cure,current,"
strWords = strWords & "curtain,custom,cut,damage,dance,danger,dark,date,daughter,day,dead,deaf,deal,dear,"
strWords = strWords & "debate,debt,decide,declare,decrease,deep,defeat,defend,deficit,define,degree,delay,"
strWords = strWords & "delicate,demand,democracy,demonstrate,denounce,deny,depend,deploy,depression,"
strWords = strWords & "describe,desert,design,desire,destroy,detail,develop,device,dictator,die,diet,"
strWords = strWords & "different,dig,dinner,diplomat,direct,direction,dirt,disappear,disarm,discover,"
strWords = strWords & "discuss,disease,disk,dismiss,dispute,dissident,distance,divide,do,doctor,document,"
strWords = strWords & "dog,dollar,door,doubt,down,drain,dream,dress,drink,drive,drop,drug,dry,during,dust,"
strWords = strWords & "duty,each,ear,early,earn,earth,ease,east,easy,eat,ecology,economy,edge,education,"
strWords = strWords & "effect,effort,egg,eight,either,elastic,electricity,eleven,else,embassy,emergency,"
strWords = strWords & "emotion,employ,empty,end,enemy,energy,enforce,engine,engineer,enjoy,enough,enter,"
strWords = strWords & "environment,equal,equipment,escape,especially,establish,estimate,ethnic,evaporate,"
strWords = strWords & "even,event,ever,every,evidence,evil,examine,example,excellent,except,exchange,"
strWords = strWords & "excuse,execute,exercise,exile,exist,expand,expect,experience,experiment,expert,"
strWords = strWords & "explain,explode,explore,export,express,extend,extra,extreme,eye,face,fact,factory,"
strWords = strWords & "fail,fair,fall,false,family,famous,far,fast,fat,father,fear,feather,feed,feel,"
strWords = strWords & "female,fertile,few,field,fierce,fifteen,fifth,fifty,fight,fill,film,final,finance,"
strWords = strWords & "find,fine,finger,finish,fire,firm,first,fish,fist,fit,five,fix,flag,flat,float,"
strWords = strWords & "floor,flow,flower,fluid,fly,fog,follow,food,fool,foolish,foot,for,forbid,force,"
strWords = strWords & "foreign,forest,forget,forgive,form,former,forty,forward,four,frame,free,freedom,"
strWords = strWords & "freeze,fresh,friend,frighten,from,front,fruit,fuel,full,fun,future,gain,game,garden,"
strWords = strWords & "gas,gather,general,get,gift,girl,give,glass,go,goal,god,gold,good,govern,government,"
strWords = strWords & "grass,great,green,grey,ground,group,grow,guarantee,guard,guide,guilty,gun,hair,half,"
strWords = strWords & "halt,hand,hang,happen,happy,hard,harmony,hat,hate,have,he,head,headquarters,heal,"
strWords = strWords & "health,healthy,hear,heart,heat,heavy,helicopter,help,her,here,hers,hide,high,hijack,"
strWords = strWords & "hill,him,his,history,hit,hold,hole,holiday,hollow,holy,home,honest,honor,hope,"
strWords = strWords & "horrible,horse,hospital,hostage,hostile,hot,hotel,hour,house,how,however,huge,human,"
strWords = strWords & "humor,hundred,hunger,hunt,hurry,hurt,husband,I,ice,idea,identify,if,ill,illegal,"
strWords = strWords & "imagine,immediate,import,important,improve,in,incident,include,increase,independent,"
strWords = strWords & "individual,industry,infect,inflation,influence,inform,information,inject,injure,"
strWords = strWords & "innocent,insane,inspect,instead,instrument,insult,insurance,intelligence,intense,"
strWords = strWords & "interest,interfere,international,into,invade,invent,invest,investigate,invite,"
strWords = strWords & "involve,iron,island,issue,it,jacket,jail,jewel,job,join,joint,joke,judge,jump,jury,"
strWords = strWords & "just,keep,key,kick,kill,kind,kiss,kit,knife,know,knowledge,labor,laboratory,lack,"
strWords = strWords & "lake,land,language,large,last,late,laugh,law,lead,leak,learn,leave,left,leg,legal,"
strWords = strWords & "lend,less,letter,level,library,lie,life,lift,light,like,limit,line,link,lip,liquid,"
strWords = strWords & "list,listen,little,live,load,loan,local,lock,long,look,loose,lose,loud,love,low,"
strWords = strWords & "loyal,luck,machine,magazine,mail,main,majority,make,male,man,manufacture,many,map,"
strWords = strWords & "march,mark,market,marry,match,material,matter,may,mayor,meal,mean,measure,meat,"
strWords = strWords & "media,medicine,meet,member,memory,mental,mercy,message,metal,method,middle,might,"
strWords = strWords & "military,milk,million,mind,mine,minister,minor,minute,miss,mist,mistake,mix,mob,"
strWords = strWords & "model,moderate,modern,money,month,moon,moral,more,morning,most,mother,mountain,"
strWords = strWords & "mouth,move,movie,much,murder,muscle,music,must,my,mystery,nail,name,narrow,nation"
strWords = strWords & ",native,natural,navy,near,necessary,neck,neither,nerve,neutral,never,new,news,next,"
strWords = strWords & "nice,night,nine,ninth,no,noise,nominate,noon,normal,north,nose,not,note,nothing,now,"
strWords = strWords & "nowhere,nuclear,number,obey,object,observe,occupy,ocean,of,off,offensive,offer,"
strWords = strWords & "office,officer,official,often,oil,old,on,once,one,only,open,operate,opinion,"
strWords = strWords & "opposite,oppress,or,orange,order,organize,other,our,ours,oust,out,over,owe,own,"
strWords = strWords & "page,pain,paint,pan,pants,paper,parade,parallel,parcel,parent,parliament,part,party,"
strWords = strWords & "pass,passenger,passport,past,paste,path,patient,pay,peace,pen,pencil,people,percent,"
strWords = strWords & "perfect,perform,period,permanent,permit,person,physical,picture,piece,pig,pilot,"
strWords = strWords & "pipe,place,plan,plant,plastic,plate,play,please,plenty,pocket,point,poison,police,"
strWords = strWords & "policy,politics,pollute,poor,popular,population,port,position,possess,possible,"
strWords = strWords & "postpone,potato,pour,powder,power,praise,pray,pregnant,present,president,press,"
strWords = strWords & "pressure,prevent,price,print,prison,private,prize,probable,problem,process,produce,"
strWords = strWords & "professor,profit,program,progress,project,property,propose,protect,protest,prove,"
strWords = strWords & "provide,public,publish,pull,punish,purchase,pure,purpose,push,put,quality,question,"
strWords = strWords & "quick,quiet,quit,race,radar,radiation,radio,raid,rail,rain,raise,rare,rate,ray,"
strWords = strWords & "reach,react,read,ready,real,realistic,reason,receive,recession,recognize,record,"
strWords = strWords & "recover,red,reduce,refugee,refuse,regret,reject,relation,release,religion,remain,"
strWords = strWords & "remember,remove,repair,repeat,report,represent,request,require,rescue,research,"
strWords = strWords & "resign,resist,resolution,resource,respect,responsible,rest,restrain,result,retire,"
strWords = strWords & "return,revolt,reward,rice,rich,ride,right,riot,rise,risk,river,road,rob,rock,rocket,"
strWords = strWords & "roll,roof,room,root,rope,rough,round,rubber,ruin,rule,run,sabotage,sacrifice,sad,"
strWords = strWords & "safe,sail,salt,same,sand,satellite,satisfy,save,say,scale,school,science,sea,search,"
strWords = strWords & "season,seat,second,secret,security,see,seek,seem,seize,seldom,self,sell,senate,send,"
strWords = strWords & "sense,sentence,separate,series,serious,serve,set,settle,seven,several,severe,sex,"
strWords = strWords & "shade,shake,shall,shame,shape,share,sharp,she,shelf,shell,shelter,shine,ship,shirt,"
strWords = strWords & "shock,shoe,shoot,short,should,shout,show,shrink,shut,sick,side,sign,signal,silence,"
strWords = strWords & "silk,silver,similar,simple,since,sing,single,sister,sit,situation,six,size,skeleton,"
strWords = strWords & "skill,skin,skirt,sky,slave,sleep,slide,slip,slow,small,smash,smell,smile,smoke,"
strWords = strWords & "smooth,snake,sneeze,snow,so,soap,social,society,soft,soil,soldier,solid,solve,some,"
strWords = strWords & "son,soon,sort,soul,sound,south,space,speak,special,speech,speed,spend,spirit,sport,"
strWords = strWords & "spread,spring,spy,square,stand,star,start,starve,station,statue,stay,steal,steam,"
strWords = strWords & "steel,step,stick,still,stomach,stone,stop,store,storm,story,straight,strange,street,"
strWords = strWords & "stretch,strike,strong,structure,struggle,study,stupid,subject,substance,substitute,"
strWords = strWords & "succeed,such,sudden,suffer,sugar,suggest,summer,sun,supervise,supply,support,"
strWords = strWords & "suppose,suppress,sure,surface,surprise,surrender,surround,survive,suspect,suspend,"
strWords = strWords & "swallow,swear,sweet,swim,sympathy,system,table,tail,take,talk,tall,target,taste,tax,"
strWords = strWords & "tea,teach,team,tear,technical,technology,telephone,television,tell,ten,term,"
strWords = strWords & "terrible,territory,terror,test,than,thank,that,the,theater,their,theirs,them,then,"
strWords = strWords & "theory,there,these,they,thick,thin,thing,think,third,thirteen,thirty,this,though,"
strWords = strWords & "thought,thousand,threaten,three,through,throw,tie,tight,time,tin,tired,to,today,"
strWords = strWords & "together,tomorrow,tongue,tonight,too,tool,tooth,top,torture,total,touch,toward,town,"
strWords = strWords & "trade,tradition,traffic,train,transport,travel,treason,treasure,treat,treatment,"
strWords = strWords & "treaty,tree,trial,tribe,trick,trip,troop,trouble,truck,true,trust,try,tube,turn"
strWords = strWords & ",twelve,twenty,twice,two,under,understand,unite,universe,university,unless,until,up,"
strWords = strWords & "urge,urgent,us,use,usual,valley,value,vegetable,vehicle,version,very,veto,vicious,"
strWords = strWords & "victim,victory,village,violate,violence,visit,voice,vote,wage,wait,walk,wall,want,"
strWords = strWords & "war,warm,warn,wash,waste,watch,water,wave,way,we,weak,wealth,weapon,wear,weather,"
strWords = strWords & "week,weight,welcome,well,west,wet,what,wheat,wheel,when,where,which,while,white,who,"
strWords = strWords & "whole,why,wide,wife,wild,will,win,wind,window,wine,wing,winter,wire,wise,wish,with,"
strWords = strWords & "withdraw,without,woman,wonder,wonderful,wood,wool,word,work,world,worry,worse,worth,"
strWords = strWords & "wound,wreck,write,wrong,year,yellow,yes,yesterday,yet,you,young,your,yours,zero"

' The following lines add words from the 500 most-common English words
' (per http://www.world-english.org/english500.htm) not found in the Globish list. Uncomment to use.
' strWords = strWords & "am,an,are,beauty,been,began,brought,came,check,children,class,could,course,cross,"
' strWords = strWords & "did,differ,does,done,don't,draw,farm,feet,figure,found,gave,got,had,has,heard,inch,is,king,knew,"
' strWords = strWords & "lay,let,lot,made,me,men,mile,need,notice,noun,numeral,oh,pattern,perhaps,plain,plane,pose,pound,product,"
' strWords = strWords & "ran,said,saw,song,spell,state,stood,those,told,took,unit,vowel,was,went,were,would"

With ActiveDocument
  With .Range
    .LanguageID = wdGerman
      With .Find
      .Replacement.ClearFormatting
      .Replacement.Text = "^&"
      .LanguageID = wdGerman
      .Forward = True
      .Wrap = wdFindContinue
      .Format = True
      .MatchCase = False
      .MatchWholeWord = True
      .MatchWildcards = False
      .MatchSoundsLike = False
      .MatchAllWordForms = True
    End With
    For i = 0 To UBound(Split(strWords, ","))
     .Find.Text = Split(strWords, ",")(i)
      Do While .Find.Execute
        .Paragraphs.First.Range.LanguageID = wdEnglishUK
        .Collapse wdCollapseEnd
      Loop
    Next i
  End With
End With
Application.ScreenUpdating = False
End Sub
You may also be interested in: https://www.msofficeforums.com/66233-post12.html
__________________
Cheers,
Paul Edstein
[Fmr MS MVP - Word]
Reply With Quote
  #3  
Old 01-12-2023, 06:10 AM
Alyb Alyb is offline Language detection Mac OS X Language detection Office 2016 for Mac
Novice
Language detection
 
Join Date: Jan 2023
Posts: 4
Alyb is on a distinguished road
Default

Thank you, Paul. What a nice solution. I found that I had to reduce the list, because of some words that are identical in German and English.

Is there an easy way to load strWords from a text file or Word document?
Reply With Quote
  #4  
Old 01-12-2023, 06:28 AM
macropod's Avatar
macropod macropod is offline Language detection Windows 10 Language detection Office 2016
Administrator
 
Join Date: Dec 2010
Location: Canberra, Australia
Posts: 21,962
macropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond reputemacropod has a reputation beyond repute
Default

Quote:
Originally Posted by Alyb View Post
Is there an easy way to load strWords from a text file or Word document?
Additional code could be used for that, but why bother since I've already included them in the existing code... You can easily-enough delete any words that occur in both languages.
__________________
Cheers,
Paul Edstein
[Fmr MS MVP - Word]
Reply With Quote
Reply



Similar Threads
Thread Thread Starter Forum Replies Last Post
Powerpoint language detection settings Roser Barcelo PowerPoint 1 05-18-2018 08:24 AM
Newbie question : detection of conflicting tasks Blitz Visio 1 03-03-2016 10:56 AM
Automatic supplier contact detection at Outlook and Lync LordLA Outlook 0 07-30-2015 02:40 AM
Language detection For techies - forensic detection advice needed please Donald Word 1 04-14-2011 04:22 PM
automatic requirement numbering with change detection stijnos Word 0 05-13-2009 12:10 AM

Other Forums: Access Forums

All times are GMT -7. The time now is 07:38 PM.


Powered by vBulletin® Version 3.8.11
Copyright ©2000 - 2024, vBulletin Solutions Inc.
Search Engine Optimisation provided by DragonByte SEO (Lite) - vBulletin Mods & Addons Copyright © 2024 DragonByte Technologies Ltd.
MSOfficeForums.com is not affiliated with Microsoft