'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 2 June 2002 at 8:17:18 pm'! Object subclass: #GoogleSpellChecker instanceVariableNames: 'licenseKey doSpellingSuggestion suggestions selectedSpellingRequest selectedSpellingSuggestion ' classVariableNames: '' poolDictionaries: '' category: 'SOAP-GoogleWebAPI'! GoogleSpellChecker class instanceVariableNames: 'licenseKey callEntry targetObjectURI namespace host port ignoreWords specialIgnoreWords '! !GoogleSpellChecker methodsFor: 'initialize-release' stamp: 'minami 5/29/2002 03:45'! initialize selectedSpellingRequest := 0. selectedSpellingSuggestion := 0! ! !GoogleSpellChecker methodsFor: 'interface opening' stamp: 'minami 6/2/2002 20:01'! showSuggestions | topWindow missSpellList suggestionList | topWindow := (SystemWindow labelled: self defaultTitle) model: self. missSpellList := PluggableListMorph on: self list: #spellingRequests selected: #selectedSpellingRequest changeSelected: #selectedSpellingRequest: menu: nil keystroke: nil. missSpellList autoDeselect: false. suggestionList := PluggableListMorph on: self list: #spellingSuggestions selected: #selectedSpellingSuggestion changeSelected: #selectedSpellingSuggestion: menu: nil keystroke: nil. suggestionList autoDeselect: false. topWindow addMorph: missSpellList frame: (0.0 @ 0.0 extent: 0.5 @ 1.0). topWindow addMorph: suggestionList frame: (0.5 @ 0.0 extent: 0.5 @ 1.0). topWindow openInWorldExtent: 300 @ 400. ^ topWindow! ! !GoogleSpellChecker methodsFor: 'actions' stamp: 'minami 5/29/2002 01:58'! spellCheck: aStream | phrases | phrases := self buildPhrases: aStream. self getSuggestions: phrases. self suggestions keys size < 1 ifTrue: [PopUpMenu inform: 'No suggestion'] ifFalse: [self showSuggestions]! ! !GoogleSpellChecker methodsFor: 'actions' stamp: 'minami 5/15/2002 00:35'! spellingSuggestionOf: phrase | params resp | params := OrderedCollection with: self licenseKey. params add: phrase. resp := self doSpellingSuggestion invokeWithValues: params. ^ resp isFault ifTrue: [resp raiseException] ifFalse: [resp returnValue]! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! callEntry ^ self class callEntry! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! doSpellingSuggestion doSpellingSuggestion isNil ifTrue: [doSpellingSuggestion := self buildDoSpellingSuggestion]. ^ doSpellingSuggestion! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:51'! licenseKey licenseKey isNil ifTrue: [licenseKey := self class licenseKey]. ^ licenseKey! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:51'! licenseKey: key licenseKey := key! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/29/2002 02:15'! spellingRequests ^ self suggestions keys asArray! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/29/2002 02:15'! spellingSuggestions ^ self suggestions values asArray! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/29/2002 01:48'! suggestions suggestions isNil ifTrue: [suggestions := Dictionary new]. ^ suggestions! ! !GoogleSpellChecker methodsFor: 'accessing' stamp: 'minami 5/29/2002 01:48'! suggestions: aDictionary suggestions := aDictionary! ! !GoogleSpellChecker methodsFor: 'constants' stamp: 'minami 5/19/2002 05:02'! defaultTitle ^ 'Google Spell Checker'! ! !GoogleSpellChecker methodsFor: 'constants' stamp: 'minami 5/15/2002 02:33'! maximumNumberOfWords ^ 10! ! !GoogleSpellChecker methodsFor: 'constants' stamp: 'minami 5/15/2002 13:36'! minimumWordLength ^ 3! ! !GoogleSpellChecker methodsFor: 'constants' stamp: 'minami 5/15/2002 13:49'! replaceString ^ ' '! ! !GoogleSpellChecker methodsFor: 'request list' stamp: 'minami 5/29/2002 02:22'! selectedSpellingRequest (self spellingRequests isNil or: [self spellingRequests size = 0]) ifTrue: [^ 0]. ^ selectedSpellingRequest! ! !GoogleSpellChecker methodsFor: 'request list' stamp: 'minami 5/29/2002 03:41'! selectedSpellingRequest: anInteger selectedSpellingRequest = anInteger ifTrue: [selectedSpellingRequest := 0] ifFalse: [selectedSpellingRequest := anInteger]. self changed: #selectedSpellingRequest! ! !GoogleSpellChecker methodsFor: 'request functions' stamp: 'minami 5/29/2002 03:00'! copyRequestSpelling self selectedSpellingRequest = 0 ifTrue: [^ self]. Clipboard clipboardText: (self spellingRequests at: self selectedSpellingRequest) asText! ! !GoogleSpellChecker methodsFor: 'request functions' stamp: 'minami 5/29/2002 03:55'! copySelectedRequestSpelling self selectedSpellingRequest = 0 ifTrue: [^ self]. Clipboard clipboardText: (self spellingRequests at: self selectedSpellingRequest) asString asText! ! !GoogleSpellChecker methodsFor: 'request functions' stamp: 'minami 5/29/2002 03:58'! requestListMenu: aMenu aMenu addList: #( #('copy' copySelectedRequestSpelling) ). ^ aMenu! ! !GoogleSpellChecker methodsFor: 'suggestion list' stamp: 'minami 5/29/2002 02:22'! selectedSpellingSuggestion (self spellingSuggestions isNil or: [self spellingSuggestions size = 0]) ifTrue: [^ 0]. ^ selectedSpellingSuggestion! ! !GoogleSpellChecker methodsFor: 'suggestion list' stamp: 'minami 5/29/2002 03:41'! selectedSpellingSuggestion: anInteger selectedSpellingSuggestion = anInteger ifTrue: [selectedSpellingSuggestion := 0] ifFalse: [selectedSpellingSuggestion := anInteger]. self changed: #selectedSpellingSuggestion! ! !GoogleSpellChecker methodsFor: 'suggestion functions' stamp: 'minami 5/29/2002 03:55'! copySelectedSuggestionSpelling self selectedSpellingRequest = 0 ifTrue: [^ self]. Clipboard clipboardText: (self spellingRequests at: self selectedSpellingRequest) asString asText! ! !GoogleSpellChecker methodsFor: 'suggestion functions' stamp: 'minami 5/29/2002 03:58'! suggestionListMenu: aMenu aMenu addList: #( #('copy' copySelectedSuggestionSpelling) ). ^ aMenu! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 5/15/2002 00:50'! buildDoSpellingSuggestion | call | call := self newCall. call methodName: 'doSpellingSuggestion'. call addParameterNamed: #key. call addParameterNamed: #phrase. ^ call! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 5/17/2002 02:44'! buildPhrases: aStream | words phrases | words := self divideIntoWords: aStream. phrases := self wordsToPhrases: words. ^ phrases! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 5/29/2002 02:10'! divideIntoWords: aStream | tokens contents col replaceDic pre | contents := aStream contents. self class specialIgnoreWords do: [:each | contents := contents copyReplaceAll: each with: ' ']. replaceDic := Dictionary new. pre := nil. contents do: [ :each | pre isNil ifFalse: [ (each isUppercase and: [pre isLowercase]) ifTrue: [replaceDic at: (pre asString , each asString) put: (pre asString , ' ' , each asString)]]. pre := each copy. ]. replaceDic keysAndValuesDo: [:key :value | contents := contents copyReplaceAll: key with: value]. tokens := Scanner new scanTokens: contents asLowercase. col := tokens reject: [:each | each isNumber]. col := col select: [:each | each first isLetter]. col := col select: [:each | each size >= self minimumWordLength ]. col := col reject: [:each | self class ignoreWords includes: each]. ^ col asSet asSortedCollection! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 6/2/2002 19:54'! getSuggestions: phrases phrases do: [:each | | retValue | retValue _ self spellingSuggestionOf: each. (retValue isNil or: [retValue = '']) ifFalse: [| keys values | keys _ Scanner new scanTokens: each. values _ Scanner new scanTokens: retValue. 1 to: keys size do: [:index | | key value | key _ keys at: index. value _ values at: index. key = value ifFalse: [self suggestions at: key put: value]]]]! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 5/15/2002 00:50'! newCall | call | call := self callEntry newCall. call targetObjectURI: self class targetObjectURI. call namespace: self class namespace. ^ call! ! !GoogleSpellChecker methodsFor: 'private' stamp: 'minami 5/17/2002 02:49'! wordsToPhrases: words | count phrases phrase | count := 0. phrases := OrderedCollection new. phrase := WriteStream on: String new. words do: [:each | phrase nextPutAll: each asString , ' '. count := count + 1. count >= self maximumNumberOfWords ifTrue: [phrases add: phrase contents. count := 0. phrase := WriteStream on: String new]]. phrase contents size > 0 ifTrue: [phrases add: phrase contents]. ^ phrases! ! !GoogleSpellChecker class methodsFor: 'instance creation' stamp: 'minami 5/29/2002 02:40'! new ^ super new initialize! ! !GoogleSpellChecker class methodsFor: 'class initialization' stamp: 'minami 5/17/2002 02:45'! initialize "GoogleSpellChecker initialize" "GoogleSpellChecker licenseKey: 'your key' (see the 'documentation' category first)" licenseKey := '00000000000000000000000000000000'. callEntry := targetObjectURI := namespace := host := port := nil. ignoreWords := specialIgnoreWords := nil! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! callEntry callEntry isNil ifTrue: [callEntry := SoapCallEntry tcpHost: self host port: self port]. ^ callEntry! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! callEntry: aValue callEntry := aValue! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! host host isNil ifTrue: [host := 'api.google.com']. ^ host! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! host: aValue host := aValue! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 13:56'! ignoreWords ignoreWords isNil ifTrue: [ignoreWords := self privIgnoreWords]. ^ ignoreWords! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 13:44'! ignoreWords: aCollection ignoreWords := aCollection! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! licenseKey ^ licenseKey! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 6/2/2002 20:13'! licenseKey: aString "GoogleSpellChecker licenseKey: 'your key'" licenseKey := aString! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! namespace namespace isNil ifTrue: [namespace := 'urn:GoogleSearch']. ^ namespace! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! namespace: aValue namespace := aValue! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! port port isNil ifTrue: [port := 80]. ^ port! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! port: aValue port := aValue! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 14:11'! specialIgnoreWords specialIgnoreWords isNil ifTrue: [specialIgnoreWords := self privSpecialIgnoreWords]. ^ specialIgnoreWords! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 14:12'! specialIgnoreWords: aCollection specialIgnoreWords := aCollection! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! targetObjectURI targetObjectURI isNil ifTrue: [targetObjectURI := 'http://api.google.com/search/beta2']. ^ targetObjectURI! ! !GoogleSpellChecker class methodsFor: 'accessing' stamp: 'minami 5/15/2002 00:50'! targetObjectURI: aValue targetObjectURI := aValue! ! !GoogleSpellChecker class methodsFor: 'private' stamp: 'minami 5/16/2002 18:46'! privIgnoreWords "GoogleSpellChecker initialize" ^ #( #absent #all #and #as #at #class #col #collect #collection #contents #context #copy #detect #dic #dictionary #do #each #error #false #first #from #includes #inject #into #is #key #last #max #minimum #name #new #nil #not #number #object #on #or #pool #pre #priv #put #reject #replace #select #self #size #stream #str #string #subclass #this #tmp #to #true #value #values #with )! ! !GoogleSpellChecker class methodsFor: 'private' stamp: 'minami 5/17/2002 03:01'! privSpecialIgnoreWords "GoogleSpellChecker initialize" ^ #( '$' ':' '(' ')' '''' '"' )! ! !ParagraphEditor methodsFor: 'google api' stamp: 'minami 5/22/2002 18:53'! spellCheckIt self lineSelectAndEmptyCheck: [^ '']. GoogleSpellChecker new spellCheck: (WriteStream with: self selection string). ! ! !ParagraphEditor class methodsFor: 'class initialization' stamp: 'minami 5/15/2002 01:07'! initializeTextEditorMenus "Initialize the yellow button pop-up menu and corresponding messages." "ParagraphEditor initializeTextEditorMenus" TextEditorYellowButtonMenu _ SelectionMenu labels: 'find...(f) find again (g) set search string (h) do again (j) undo (z) copy (c) cut (x) paste (v) paste... do it (d) print it (p) inspect it (i) explore it (I) debug it spell check it accept (s) cancel (l) show bytecodes more...' lines: #(3 5 9 14 15 17 18) selections: #(find findAgain setSearchString again undo copySelection cut paste pasteRecent doIt printIt inspectIt exploreIt debugIt spellCheckIt accept cancel showBytecodes shiftedTextPaneMenuRequest).! ! !PluggableTextMorph methodsFor: 'google api' stamp: 'minami 5/15/2002 02:45'! spellCheckIt self handleEdit: [textMorph editor spellCheckIt]! ! GoogleSpellChecker initialize! ParagraphEditor initialize.