SystemOrganization addCategory: #'OB-Regex-Tools'! SystemOrganization addCategory: #'OB-Regex-Commands'! Refactoring subclass: #ORRegexRefactoring instanceVariableNames: 'matchers' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Tools'! ORRegexRefactoring subclass: #ORCategoryRegexRefactoring instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Tools'! !ORCategoryRegexRefactoring methodsFor: 'transforming' stamp: 'lr 3/1/2009 09:30'! transform | replacement | self model allClassesDo: [ :class | (class isNil or: [ class isMeta ]) ifFalse: [ replacement := self execute: class category. replacement = class category asString ifFalse: [ class category: replacement. self model defineClass: class definitionString ] ] ]! ! ORRegexRefactoring subclass: #ORClassRegexRefactoring instanceVariableNames: 'rootClass mode' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Tools'! !ORClassRegexRefactoring methodsFor: 'transforming' stamp: 'lr 5/30/2008 13:14'! copy: aClass name: aSymbol ^ self duplicate: aClass name: aSymbol deep: true! ! !ORClassRegexRefactoring methodsFor: 'actions' stamp: 'lr 5/30/2008 13:15'! copyClasses mode := #copy:name:! ! !ORClassRegexRefactoring methodsFor: 'private' stamp: 'lr 5/30/2008 13:23'! copyFrom: aSourceClass to: aTargetClass aSourceClass instanceVariableNames do: [ :each | aTargetClass addInstanceVariable: each ]. aSourceClass isMeta ifFalse: [ aSourceClass allClassVariableNames do: [ :each | aTargetClass addClassVariable: each ]. aSourceClass poolDictionaryNames do: [ :each | aTargetClass addPoolDictionary: each ] ]. aSourceClass selectors do: [ :each | aTargetClass compile: (aSourceClass sourceCodeFor: each) classified: (aSourceClass protocolsFor: each) ]! ! !ORClassRegexRefactoring methodsFor: 'transforming' stamp: 'lr 5/30/2008 13:15'! create: aClass name: aSymbol ^ self duplicate: aClass name: aSymbol deep: false! ! !ORClassRegexRefactoring methodsFor: 'actions' stamp: 'lr 5/30/2008 13:15'! createClasses mode := #create:name:! ! !ORClassRegexRefactoring methodsFor: 'private' stamp: 'lr 10/26/2009 22:22'! duplicate: aClass name: aSymbol deep: aBoolean | superclass superclassName name class | (self model includesClassNamed: aSymbol) ifTrue: [ ^ nil ]. superclass := aClass superclass ifNil: [ self rootClass ]. superclassName := (self model includesClassNamed: superclass name) ifFalse: [ superclass name ] ifTrue: [ (name := self execute: superclass name) = superclass name ifFalse: [ self duplicate: superclass name: name deep: aBoolean ]. name ]. self model defineClass: ('<1s> subclass: #<2s> instanceVariableNames: '''' classVariableNames: '''' poolDictionaries: '''' category: <3p>' expandMacrosWith: superclassName with: aSymbol with: aClass category asString). aBoolean ifTrue: [ (class := self model classNamed: aSymbol) ifNil: [ ^ self ]. self copyFrom: aClass to: class. self copyFrom: aClass theMetaClass to: class theMetaClass ]. ^ nil! ! !ORClassRegexRefactoring methodsFor: 'initialization' stamp: 'lr 5/30/2008 11:46'! initialize super initialize. self createClasses! ! !ORClassRegexRefactoring methodsFor: 'transforming' stamp: 'lr 5/30/2008 13:15'! rename: aClass name: aSymbol ^ RenameClassRefactoring model: self model rename: aClass to: aSymbol! ! !ORClassRegexRefactoring methodsFor: 'actions' stamp: 'lr 5/30/2008 13:15'! renameClasses mode := #rename:name:! ! !ORClassRegexRefactoring methodsFor: 'accessing' stamp: 'lr 5/30/2008 13:51'! rootClass ^ rootClass ifNil: [ Object ]! ! !ORClassRegexRefactoring methodsFor: 'initialization' stamp: 'lr 10/26/2009 22:23'! rootClass: aClass rootClass := aClass theNonMetaClass! ! !ORClassRegexRefactoring methodsFor: 'transforming' stamp: 'lr 3/1/2009 09:30'! transform | replacement refactoring | self model allClassesDo: [ :class | (class isNil or: [ class isMeta ]) ifFalse: [ replacement := self execute: class name. replacement = class name asString ifFalse: [ refactoring := self perform: mode with: class with: replacement asSymbol. (refactoring notNil and: [ refactoring preconditions check ]) ifTrue: [ refactoring transform ] ] ] ]! ! ORRegexRefactoring subclass: #ORProtocolRegexRefactoring instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Tools'! !ORProtocolRegexRefactoring methodsFor: 'transforming' stamp: 'lr 3/1/2009 09:30'! transform | original replacement | self model allClassesDo: [ :class | class selectors do: [ :selector | original := (class realClass whichCategoryIncludesSelector: selector) asString. original isNil ifFalse: [ replacement := self execute: original. replacement = original ifFalse: [ class compile: (class sourceCodeFor: selector) classified: replacement ] ] ] ]! ! !ORRegexRefactoring methodsFor: 'private' stamp: 'lr 3/1/2009 09:34'! execute: aString "Perform all searches on aString and return the transformation." ^ matchers inject: aString asString into: [ :string :assoc | self execute: string replace: assoc key with: assoc value ]! ! !ORRegexRefactoring methodsFor: 'private' stamp: 'lr 3/1/2009 09:29'! execute: aString replace: aRegex with: aReadStream | stream | ^ aRegex copy: aString translatingMatchesUsing: [ :match | stream := WriteStream on: (String new: 2 * aString size). [ aReadStream atEnd ] whileFalse: [ stream nextPutAll: (aReadStream upTo: $$). aReadStream atEnd ifFalse: [ aReadStream peek isDigit ifFalse: [ stream nextPut: aReadStream next ] ifTrue: [ stream nextPutAll: (aRegex subexpression: aReadStream next asInteger - $0 asInteger + 1) ] ] ]. aReadStream reset. stream contents ]! ! !ORRegexRefactoring methodsFor: 'initialize' stamp: 'lr 3/1/2009 09:16'! initialize super initialize. matchers := OrderedCollection new! ! !ORRegexRefactoring methodsFor: 'preconditions' stamp: 'lr 2/3/2008 22:02'! preconditions ^ RBCondition empty! ! !ORRegexRefactoring methodsFor: 'searching' stamp: 'lr 3/1/2009 09:14'! replace: aFindString with: aReplaceString self replace: aFindString with: aReplaceString ignoreCase: false! ! !ORRegexRefactoring methodsFor: 'searching' stamp: 'lr 3/1/2009 09:17'! replace: aFindString with: aReplaceString ignoreCase: aBoolean "Replace all matches of aFindString (regular expression) with aReplaceString, where $0 references the whole match, and $1..$9 the matched groups." | regex stream | regex := RxParser preferredMatcherClass for: (RxParser new parse: aFindString) ignoreCase: aBoolean. stream := aReplaceString readStream. matchers add: regex -> stream! ! ORRegexRefactoring subclass: #ORSourceRegexRefactoring instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Tools'! !ORSourceRegexRefactoring methodsFor: 'private' stamp: 'lr 2/4/2008 09:28'! parseMethod: aString ^ [ RBParser parseMethod: aString ] on: Error do: [ :err | nil ]! ! !ORSourceRegexRefactoring methodsFor: 'private' stamp: 'lr 2/4/2008 09:29'! parseSelector: aString ^ RBParser parseMethodPattern: aString! ! !ORSourceRegexRefactoring methodsFor: 'transforming' stamp: 'lr 3/1/2009 09:31'! transform | original replacement protocols | self model allClassesDo: [ :class | class selectors do: [ :selector | original := class sourceCodeFor: selector. replacement := self execute: original. replacement = original ifFalse: [ (self parseMethod: replacement) isNil ifFalse: [ protocols := class protocolsFor: selector. (self parseSelector: replacement) = selector ifFalse: [ class removeMethod: selector ]. class compile: replacement classified: protocols ] ] ] ]! ! OBDefinition subclass: #OROpenRegexDefinition instanceVariableNames: 'command text' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !OROpenRegexDefinition class methodsFor: 'instance-creation' stamp: 'lr 4/2/2009 14:43'! on: aCommand ^ self new initializeOn: aCommand! ! !OROpenRegexDefinition methodsFor: 'accessing' stamp: 'lr 4/2/2009 14:43'! accept: aText notifying: aController | refactoring | text := aText asString. refactoring := self class evaluatorClass evaluate: text for: self notifying: aController logged: false. refactoring model environment: command environment. command performRefactoring: refactoring. ^ true! ! !OROpenRegexDefinition methodsFor: 'initialization' stamp: 'lr 4/2/2009 14:42'! initializeOn: aCommand command := aCommand. text := aCommand template! ! !OROpenRegexDefinition methodsFor: 'accessing' stamp: 'lr 4/26/2010 16:15'! shouldBeStyledBy: aPluggableShoutMorph aPluggableShoutMorph classOrMetaClass: nil. ^ true! ! !OROpenRegexDefinition methodsFor: 'accessing' stamp: 'lr 3/4/2009 22:12'! text ^ text! ! !OBCodeBrowser methodsFor: '*ob-regex-commands' stamp: 'lr 2/24/2009 14:17'! cmdRegex ^ ORCmdRegex allSubclasses! ! !OBCodeBrowser methodsFor: '*ob-regex-commands' stamp: 'lr 2/3/2008 21:20'! cmdRegexEnvironment ^ ORCmdRegexEnvironment allSubclasses! ! ORCommand subclass: #ORCmdRegex instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! ORCmdRegex subclass: #ORCmdCategoryRegex instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdCategoryRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 15:03'! name ^ 'category'! ! !ORCmdCategoryRegex methodsFor: 'accessing' stamp: 'lr 3/1/2009 09:41'! template ^ 'ORCategoryRegexRefactoring new replace: ''^Kernel-(.*)$'' with: ''System-$1'' ignoreCase: false; yourself'! ! ORCmdRegex subclass: #ORCmdClassRegex instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdClassRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 15:03'! name ^ 'class'! ! !ORCmdClassRegex methodsFor: 'accessing' stamp: 'lr 3/1/2009 09:41'! template ^ 'ORClassRegexRefactoring new "Example 1: Change class prefixes" renameClasses; replace: ''^AB(.*)$'' with: ''CD$1'' ignoreCase: false; "Example 2: Generate empty test classes" createClasses; rootClass: TestCase; replace: ''^.*$'' with: ''$0Test'' ignoreCase: false; "Example 3: Copy classes" copyClasses; replace: ''^.*$'' with: ''$0Plus'' ignoreCase: false; yourself'! ! ORCmdRegex subclass: #ORCmdProtocolRegex instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdProtocolRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 15:03'! name ^ 'protocol'! ! !ORCmdProtocolRegex methodsFor: 'accessing' stamp: 'lr 3/1/2009 09:46'! template ^ 'ORProtocolRegexRefactoring new replace: ''^\*system(.*)$'' with: ''*kernel$1'' ignoreCase: true; yourself'! ! !ORCmdRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 16:54'! cluster ^ #refactor! ! !ORCmdRegex methodsFor: 'execution' stamp: 'lr 2/24/2009 14:15'! definition: aDefinition requestor announce: (OBDefinitionChanged definition: aDefinition)! ! !ORCmdRegex methodsFor: 'execution' stamp: 'lr 4/2/2009 14:42'! execute self definition: (OROpenRegexDefinition on: self)! ! !ORCmdRegex methodsFor: 'accessing' stamp: 'lr 2/24/2009 14:10'! group ^ #regex! ! !ORCmdRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 15:04'! label ^ self name , ' regex'! ! !ORCmdRegex methodsFor: 'accessing' stamp: 'lr 2/24/2009 14:12'! template self subclassResponsibility! ! ORCmdRegex subclass: #ORCmdSourceRegex instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdSourceRegex methodsFor: 'accessing' stamp: 'lr 2/26/2009 15:03'! name ^ 'source'! ! !ORCmdSourceRegex methodsFor: 'accessing' stamp: 'lr 3/1/2009 09:53'! template ^ 'ORSourceRegexRefactoring new "Example 1: Replace symbols with strings" replace: ''#(\w+)'' with: ''''''$1'''''' ignoreCase: false; "Example 2: Replace 4 spaces with tabs" replace: '' '' with: '' '' ignoreCase: false; yourself'! ! ORCommand subclass: #ORCmdRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! ORCmdRegexEnvironment subclass: #ORCmdCategoryRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdCategoryRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/8/2009 19:52'! default ^ (target isKindOf: OBClassAwareNode) ifTrue: [ '/^' , (target theNonMetaClass category copyUpTo: $-) , '-.*$/' ] ifFalse: [ (target isKindOf: OBClassCategoryNode) ifTrue: [ '/^' , (target name copyUpTo: $-) , '-.*$/' ] ifFalse: [ super default ] ]! ! !ORCmdCategoryRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:55'! name ^ 'category'! ! !ORCmdCategoryRegexEnvironment methodsFor: 'execution' stamp: 'lr 2/9/2008 15:34'! search: aMatcher | categories parent | categories := Set new. parent := self environment. parent categories do: [ :category | (aMatcher matches: category) ifTrue: [ categories add: category ] ]. ^ CategoryEnvironment onEnvironment: parent categories: categories! ! ORCmdRegexEnvironment subclass: #ORCmdClassRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdClassRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/8/2009 19:54'! default ^ (target isKindOf: OBClassAwareNode) ifTrue: [ '/^' , (target theNonMetaClassName first: (2 min: target theNonMetaClassName size)) , '.*$/' ] ifFalse: [ super default ]! ! !ORCmdClassRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:55'! name ^ 'class'! ! !ORCmdClassRegexEnvironment methodsFor: 'execution' stamp: 'lr 1/28/2008 23:13'! search: aMatcher | parent environment | parent := self environment. environment := ClassEnvironment onEnvironment: parent. parent classesDo: [ :class | aMatcher matchesIn: class name do: [ :each | environment addClass: class; addSearchString: each ] ]. ^ environment! ! ORCmdRegexEnvironment subclass: #ORCmdProtocolRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdProtocolRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/1/2009 11:26'! default ^ (target hasSelector or: [ target isMethodCategoryNode ]) ifTrue: [ '/^' , (target category copyUpTo: $-) , '.*$/i' ] ifFalse: [ super default ]! ! !ORCmdProtocolRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:55'! name ^ 'protocol'! ! !ORCmdProtocolRegexEnvironment methodsFor: 'execution' stamp: 'lr 2/26/2009 14:59'! search: aMatcher | parent environment | parent := self environment. environment := SelectorEnvironment onEnvironment: parent. parent classesDo: [ :class | (parent protocolsFor: class) do: [ :protocol | (aMatcher matches: protocol) ifTrue: [ (parent selectorsFor: protocol in: class) do: [ :selector | environment addClass: class selector: selector ] ] ] ]. ^ environment! ! !ORCmdRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/8/2009 19:55'! cluster ^ #'refactoring scope'! ! !ORCmdRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/1/2009 11:27'! default ^ '/^.*$/'! ! !ORCmdRegexEnvironment methodsFor: 'execution' stamp: 'lr 12/4/2009 08:07'! execute | expression matcher environment | expression := [ self prompt: 'Search in ' , self name , ':' initialAnswer: self default ] on: ORUICancellationError do: [ :err | ^ self ]. matcher := [ self parse: expression ] on: RegexError do: [ :err | ^ self inform: err messageText ]. OBWaitRequest block: [ environment := self search: matcher. environment label: (String with: self name first asUppercase) , self name allButFirst , ' matching ' , expression ]. self openEnvironment: environment! ! !ORCmdRegexEnvironment methodsFor: 'accessing' stamp: 'lr 1/28/2008 22:25'! group ^ #regex! ! !ORCmdRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:55'! label ^ self name , ' regex...'! ! !ORCmdRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/9/2008 15:15'! name ^ self subclassResponsibility! ! !ORCmdRegexEnvironment methodsFor: 'private' stamp: 'lr 3/1/2009 11:18'! parse: aString | start stop expression options | start := aString indexOf: $/. stop := aString lastIndexOf: $/. start + 1 < stop ifFalse: [ RegexSyntaxError signal: 'Empty regular expression' ]. expression := aString copyFrom: start + 1 to: stop - 1. options := aString copyFrom: stop + 1 to: aString size. ^ RxParser preferredMatcherClass for: (RxParser parse: expression) ignoreCase: (options asLowercase includes: $i)! ! !ORCmdRegexEnvironment methodsFor: 'execution' stamp: 'lr 1/28/2008 22:52'! search: aMatcher self subclassResponsibility! ! ORCmdRegexEnvironment subclass: #ORCmdSelectorRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdSelectorRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/1/2009 11:27'! default ^ target hasSelector ifTrue: [ '/^' , target selector , '$/' ] ifFalse: [ super default ]! ! !ORCmdSelectorRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:55'! name ^ 'selector'! ! !ORCmdSelectorRegexEnvironment methodsFor: 'execution' stamp: 'lr 1/28/2008 23:16'! search: aMatcher | parent environment | parent := self environment. environment := SelectorEnvironment onEnvironment: parent. parent classesAndSelectorsDo: [ :class :selector | aMatcher matchesIn: selector do: [ :each | environment addClass: class selector: selector; addSearchString: each ] ]. ^ environment! ! ORCmdRegexEnvironment subclass: #ORCmdSourceRegexEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'OB-Regex-Commands'! !ORCmdSourceRegexEnvironment methodsFor: 'accessing' stamp: 'lr 3/1/2009 11:27'! default ^ super default , 'i'! ! !ORCmdSourceRegexEnvironment methodsFor: 'accessing' stamp: 'lr 2/26/2009 14:56'! name ^ 'source'! ! !ORCmdSourceRegexEnvironment methodsFor: 'execution' stamp: 'lr 1/28/2008 23:16'! search: aMatcher | parent environment | parent := self environment. environment := SelectorEnvironment onEnvironment: parent. parent classesAndSelectorsDo: [ :class :selector | aMatcher matchesIn: (class sourceCodeAt: selector) do: [ :each | environment addClass: class selector: selector; addSearchString: each ] ]. ^ environment! !