SystemOrganization addCategory: #'Refactoring-Spelling'! Object subclass: #RBSpellChecker instanceVariableNames: '' classVariableNames: 'Default' poolDictionaries: '' category: 'Refactoring-Spelling'! RBSpellChecker subclass: #RBInternalSpellChecker instanceVariableNames: 'words' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBInternalSpellChecker commentStamp: 'lr 2/8/2009 12:47' prior: 0! A stupid spell checker implementation, to be used in case no native spell checker is available. Uses a combined word-list of and .! !RBInternalSpellChecker class methodsFor: 'private' stamp: 'lr 1/22/2010 09:48'! createWordList: aString "The input of the wordlist can be something from ." "self createWordList: '/Users/renggli/Desktop/words.txt'" | words input output zipped | words := Set new. input := FileStream fileNamed: aString. input converter: Latin1TextConverter new. [ input atEnd ] whileFalse: [ | word | word := input upTo: Character lf. word isNil ifFalse: [ word := word withBlanksTrimmed. word size > 1 ifTrue: [ words add: word asLowercase ] ] ]. output := self basicNew directory forceNewFileNamed: self basicNew filename. zipped := ZLibWriteStream on: output binary. zipped nextInt32Put: words size. words asArray sort do: [ :each | zipped nextPut: each size; nextPutAll: (ByteArray withAll: each) ]. zipped close. output close! ! !RBInternalSpellChecker methodsFor: 'public' stamp: 'lr 1/21/2010 21:30'! check: aString ^ (self normalize: aString) reject: [ :each | self validate: each ]! ! !RBInternalSpellChecker methodsFor: 'accessing' stamp: 'lr 1/22/2010 08:04'! directory ^ FileDirectory default! ! !RBInternalSpellChecker methodsFor: 'private' stamp: 'lr 1/22/2010 09:47'! downloadData "Download data from a server." | response stream | response := HTTPSocket httpGet: self url. response isString ifTrue: [ self error: response ]. stream := self directory forceNewFileNamed: self filename. [ stream binary; nextPutAll: (response binary; contents) ] ensure: [ stream close ]! ! !RBInternalSpellChecker methodsFor: 'accessing' stamp: 'lr 1/22/2010 08:03'! filename ^ 'rb-spelling.dat'! ! !RBInternalSpellChecker methodsFor: 'initialization' stamp: 'lr 1/22/2010 08:11'! initialize super initialize. words := self loadData! ! !RBInternalSpellChecker methodsFor: 'private' stamp: 'lr 1/22/2010 09:08'! loadData "Load data from an external file as fast as possible." | result stream | (self directory fileExists: self filename) ifFalse: [ self downloadData ]. stream := self directory oldFileNamed: self filename. [ | zstream size | zstream := ZLibReadStream on: stream binary. result := Array new: (size := zstream nextInt32). 1 to: size do: [ :index | result at: index put: (String withAll: (zstream next: zstream next)) ] ] ensure: [ stream close ]. ^ result! ! !RBInternalSpellChecker methodsFor: 'public' stamp: 'lr 1/21/2010 23:25'! normalize: aString "Tokenize aString into individual words." | result input output | result := Set new. input := aString readStream. output := WriteStream on: (String new: 128). [ input atEnd ] whileFalse: [ [ input atEnd not and: [ input peek isLetter or: [ input peek = $' ] ] ] whileTrue: [ output nextPut: input next ]. [ input atEnd not and: [ input peek isLetter not ] ] whileTrue: [ input next ]. output position > 1 ifTrue: [ result add: output contents ]. result size > 10000 ifTrue: [ ^ result ]. output reset ]. ^ result! ! !RBInternalSpellChecker methodsFor: 'accessing' stamp: 'lr 1/22/2010 09:45'! url ^ 'http://www.lukas-renggli.ch/smalltalk/rb-spelling.dat'! ! !RBInternalSpellChecker methodsFor: 'public' stamp: 'lr 1/21/2010 23:20'! validate: aString "Do a binary search for the word aString. Answer true if the aString is in the list of known words." | check low high index word | check := aString asLowercase. low := 1. high := words size. [ index := low + high // 2. low <= high ] whileTrue: [ word := words at: index. word = check ifTrue: [ ^ true ]. word < check ifTrue: [ low := index + 1 ] ifFalse: [ high := index - 1 ] ]. ^ word = check! ! !RBInternalSpellChecker methodsFor: 'accessing' stamp: 'lr 3/8/2009 20:21'! words ^ words! ! RBSpellChecker subclass: #RBMacSpellChecker instanceVariableNames: '' classVariableNames: 'Utf16Converter' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBMacSpellChecker commentStamp: 'lr 2/8/2009 12:48' prior: 0! A native spell checker of the Apple OS X platform. Source code is ripped from JMMMacSpelling.1.cs by John McIntosh .! !RBMacSpellChecker class methodsFor: 'initialization' stamp: 'lr 2/8/2009 11:15'! initialize Utf16Converter := TextConverter newForEncoding: 'utf-16'! ! !RBMacSpellChecker class methodsFor: 'testing' stamp: 'lr 1/21/2010 19:06'! isSupported ^ self primitiveGetUniqueSpellingTag notNil! ! !RBMacSpellChecker class methodsFor: 'primitives' stamp: 'lr 2/8/2009 12:08'! primitiveGetUniqueSpellingTag ^ nil! ! !RBMacSpellChecker methodsFor: 'public' stamp: 'lr 1/21/2010 22:00'! check: aString | position errors string result | position := 1. errors := OrderedCollection new. string := aString convertToWithConverter: Utf16Converter. [ position <= string size ] whileTrue: [ result := self primitiveCheckSpelling: string startingAt: position. (result first between: 1 and: string size) ifFalse: [ ^ errors ]. errors addLast: (aString copyFrom: result first to: result first + result second - 1). position := result first + result second ]. ^ errors! ! !RBMacSpellChecker methodsFor: 'private' stamp: 'lr 2/8/2009 11:58'! primitiveCheckSpelling: aString startingAt: anInteger self primitiveFailed! ! !RBSpellChecker class methodsFor: 'private' stamp: 'lr 9/5/2009 23:57'! createInstance ^ RBMacSpellChecker isSupported ifTrue: [ RBMacSpellChecker new ] ifFalse: [ RBInternalSpellChecker new ]! ! !RBSpellChecker class methodsFor: 'accessing' stamp: 'lr 9/5/2009 23:57'! default ^ Default ifNil: [ Default := self createInstance ]! ! !RBSpellChecker class methodsFor: 'initialization' stamp: 'lr 9/5/2009 23:54'! initialize Smalltalk addToShutDownList: self! ! !RBSpellChecker class methodsFor: 'initialization' stamp: 'lr 2/8/2009 12:24'! shutDown Default := nil! ! !RBSpellChecker class methodsFor: 'initialization' stamp: 'lr 9/5/2009 23:54'! unload Smalltalk removeFromShutDownList: self! ! !RBSpellChecker methodsFor: 'public' stamp: 'lr 1/21/2010 18:40'! check: aString "Answer a collection of spelling errors in the receiver." ^ #()! ! RBBlockLintRule subclass: #RBSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! RBSpellingRule subclass: #RBArgumentVariableNamesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBArgumentVariableNamesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:31'! checkMethod: aContext aContext parseTree allArgumentVariables do: [ :name | (self checkIdentifier: name) do: [ :each | result addSearchString: each; addClass: aContext selectedClass selector: aContext selector ] ]! ! !RBArgumentVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Argument variable names'! ! RBSpellingRule subclass: #RBClassCategoriesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBClassCategoriesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:31'! checkClass: aContext | category | aContext selectedClass isMeta ifTrue: [ ^ self ]. category := aContext selectedClass category. (self checkSelector: category) do: [ :each | result addSearchString: each; addCategory: category ]! ! !RBClassCategoriesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Class categories'! ! !RBClassCategoriesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ CategoryEnvironment! ! RBSpellingRule subclass: #RBClassCommentsSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBClassCommentsSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:44'! checkClass: aContext | comment | aContext selectedClass isMeta ifTrue: [ ^ self ]. comment := aContext selectedClass organization classComment asString. (self check: comment) do: [ :each | result addSearchString: each; addClass: aContext selectedClass ]! ! !RBClassCommentsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Class comments'! ! !RBClassCommentsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ ClassEnvironment! ! RBSpellingRule subclass: #RBClassNamesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBClassNamesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:31'! checkClass: aContext | name | aContext selectedClass isMeta ifTrue: [ ^ self ]. name := aContext selectedClass name. (self checkIdentifier: name) do: [ :each | result addSearchString: each; addClass: aContext selectedClass ]! ! !RBClassNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Class names'! ! !RBClassNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ ClassEnvironment! ! RBSpellingRule subclass: #RBClassVariableNamesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBClassVariableNamesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 23:42'! checkClass: aContext aContext selectedClass isMeta ifTrue: [ ^ self ]. aContext selectedClass classVarNames do: [ :name | (self checkIdentifier: name) do: [ :each | result addSearchString: each; addClass: aContext selectedClass ] ]! ! !RBClassVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Class variable names'! ! !RBClassVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ ClassEnvironment! ! RBSpellingRule subclass: #RBInstanceVariableNamesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBInstanceVariableNamesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:31'! checkClass: aContext aContext selectedClass instVarNames do: [ :name | (self checkIdentifier: name) do: [ :each | result addSearchString: each; addClass: aContext selectedClass ] ]! ! !RBInstanceVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Instance variable names'! ! !RBInstanceVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ ClassEnvironment! ! RBSpellingRule subclass: #RBLiteralValuesSpellingRule instanceVariableNames: 'matcher' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBLiteralValuesSpellingRule methodsFor: 'private' stamp: 'lr 1/12/2010 11:56'! add: aLiteral to: aCollection aLiteral isString ifTrue: [ aCollection add: aLiteral ] ifFalse: [ aLiteral isArray ifTrue: [ aLiteral do: [ :each | self add: each to: aCollection ] ] ]. ^ aCollection! ! !RBLiteralValuesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:22'! checkMethod: aContext | literals | literals := matcher executeTree: aContext parseTree initialAnswer: Set new. literals do: [ :literal | (self checkLiteral: literal) do: [ :each | result addSearchString: literal; addClass: aContext selectedClass selector: aContext selector ] ]! ! !RBLiteralValuesSpellingRule methodsFor: 'initialization' stamp: 'lr 1/12/2010 11:43'! initialize super initialize. matcher := RBParseTreeSearcher new. matcher matches: '`#literal' do: [ :node :answer | self add: node value to: answer ]! ! !RBLiteralValuesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Literal values'! ! RBSpellingRule subclass: #RBMethodCommentsSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBMethodCommentsSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:24'! checkMethod: aContext aContext parseTree nodesDo: [ :node | node comments do: [ :interval | | source | source := aContext sourceCode asString copyFrom: interval first + 1 to: interval last - 1. (self check: source) do: [ :each | result addSearchString: each; addClass: aContext selectedClass selector: aContext selector ] ] ]! ! !RBMethodCommentsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Method comments'! ! RBSpellingRule subclass: #RBMethodProtocolsSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBMethodProtocolsSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:53'! checkClass: aContext | organizer | organizer := aContext selectedClass organization. organizer categories do: [ :protocol | (self checkSelector: protocol) do: [ :each | (organizer listAtCategoryNamed: protocol) do: [ :selector | result addSearchString: each; addClass: aContext selectedClass selector: selector into: protocol ] ] ]! ! !RBMethodProtocolsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Method protocols'! ! !RBMethodProtocolsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! resultClass ^ MultiEnvironment! ! RBSpellingRule subclass: #RBMethodSelectorsSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBMethodSelectorsSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:32'! checkMethod: aContext (self checkSelector: aContext selector) do: [ :each | result addSearchString: each; addClass: aContext selectedClass selector: aContext selector ]! ! !RBMethodSelectorsSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Method selectors'! ! !RBSpellingRule class methodsFor: 'testing' stamp: 'lr 2/24/2009 17:09'! isVisible ^ self name ~= #RBSpellingRule! ! !RBSpellingRule methodsFor: 'public' stamp: 'lr 1/21/2010 21:07'! check: aString ^ RBSpellChecker default check: aString! ! !RBSpellingRule methodsFor: 'public' stamp: 'lr 1/21/2010 20:43'! checkIdentifier: aString ^ self check: (self normalizeIdentifier: aString)! ! !RBSpellingRule methodsFor: 'public' stamp: 'lr 1/21/2010 21:21'! checkLiteral: aLiteral ^ self check: (self normalizeLiteral: aLiteral)! ! !RBSpellingRule methodsFor: 'public' stamp: 'lr 1/21/2010 21:06'! checkSelector: aString ^ self check: (self normalizeSelector: aString)! ! !RBSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:56'! group ^ 'Spelling'! ! !RBSpellingRule methodsFor: 'normalization' stamp: 'lr 1/23/2010 16:27'! normalizeCamelCase: aString "An ugly long method to get rid of camel case strings." | input output char | input := aString readStream. output := WriteStream on: (String new: 2 * aString size). [ input atEnd ] whileFalse: [ output nextPut: (char := input next). char isLetter ifTrue: [ [ input atEnd not and: [ input peek isLowercase ] ] whileTrue: [ output nextPut: input next ]. (input atEnd not and: [ input peek isSeparator not ]) ifTrue: [ output space ] ] ifFalse: [ char isDigit ifTrue: [ [ input atEnd not and: [ input peek isDigit ] ] whileTrue: [ output nextPut: input next ]. (input atEnd not and: [ input peek isSeparator not ]) ifTrue: [ output space ] ] ] ]. ^ output contents! ! !RBSpellingRule methodsFor: 'normalization' stamp: 'lr 1/21/2010 20:43'! normalizeIdentifier: aString ^ self normalizeCamelCase: (aString copyReplaceAll: '_' with: ' ')! ! !RBSpellingRule methodsFor: 'normalization' stamp: 'lr 1/21/2010 21:04'! normalizeLiteral: aLiteral | stream | stream := WriteStream on: String new. self normalizeLiteral: aLiteral on: stream. ^ stream contents! ! !RBSpellingRule methodsFor: 'normalization' stamp: 'lr 1/23/2010 16:45'! normalizeLiteral: aLiteral on: aStream aLiteral isSymbol ifTrue: [ ^ aStream nextPutAll: (self normalizeSelector: aLiteral) ]. aLiteral isString ifTrue: [ ^ aStream nextPutAll: aLiteral ]. aLiteral isCharacter ifTrue: [ ^ aStream nextPut: aLiteral ]. aLiteral isCollection ifTrue: [ ^ aLiteral do: [ :each | self normalizeLiteral: each on: aStream ] separatedBy: [ aStream nextPut: $ ] ]. aStream print: aLiteral! ! !RBSpellingRule methodsFor: 'normalization' stamp: 'lr 1/21/2010 20:41'! normalizeSelector: aString ^ self normalizeIdentifier: (aString copyReplaceAll: ':' with: ' ')! ! !RBSpellingRule methodsFor: 'accessing' stamp: 'lr 5/15/2010 18:05'! rationale ^ 'Checks for spelling errors in ' , self name asLowercase , '.'! ! !RBSpellingRule methodsFor: 'accessing' stamp: 'lr 5/15/2010 15:12'! severity ^ #information! ! RBSpellingRule subclass: #RBTemporaryVariableNamesSpellingRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Refactoring-Spelling'! !RBTemporaryVariableNamesSpellingRule methodsFor: 'running' stamp: 'lr 1/21/2010 21:32'! checkMethod: aContext aContext parseTree allTemporaryVariables do: [ :name | (self checkIdentifier: name) do: [ :each | result addSearchString: each; addClass: aContext selectedClass selector: aContext selector ] ]! ! !RBTemporaryVariableNamesSpellingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 07:57'! name ^ 'Temporary variable names'! ! RBMacSpellChecker initialize! RBSpellChecker initialize!