Skip to content
This repository has been archived by the owner on Jul 7, 2021. It is now read-only.

Commit

Permalink
Filing out all the packages seems to change the line endings with no …
Browse files Browse the repository at this point in the history
…otherwise discernible diff.
  • Loading branch information
James Foster committed Aug 18, 2020
1 parent d81ff71 commit 6ecc3cd
Show file tree
Hide file tree
Showing 11 changed files with 545 additions and 545 deletions.
214 changes: 107 additions & 107 deletions sources/Jade Rewrite tool.pax
Original file line number Diff line number Diff line change
@@ -1,107 +1,107 @@
| package |
package := Package name: 'Jade Rewrite tool'.
package paxVersion: 1;
basicComment: ''.

package basicScriptAt: #postinstall put: 'JadeRewriteToolPreference default formatterClass: ''RBFormatter''.'.

package classNames
add: #JadeGsMethodShape;
add: #JadeRewriteChangesBrowser;
add: #JadeRewriteMethodsList;
add: #JadeRewriteMethodsListShell;
add: #JadeRewriteReplaceMethodsList;
add: #JadeRewriteReplaceMethodsListShell;
add: #JadeRewriteSearchMethodsList;
add: #JadeRewriteSearchMethodsListShell;
add: #JadeRewriteTool;
add: #JadeRewriteToolPreference;
yourself.

package binaryGlobalNames: (Set new
yourself).

package globalAliases: (Set new
yourself).

package setPrerequisites: #(
'..\Core\Object Arts\Dolphin\IDE\Base\Development System'
'..\Core\Object Arts\Dolphin\Base\Dolphin'
'..\Core\Object Arts\Dolphin\MVP\Base\Dolphin Basic Geometry'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Boolean\Dolphin Boolean Presenter'
'..\Core\Object Arts\Dolphin\MVP\Views\Common Controls\Dolphin Common Controls'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Difference\Dolphin Differences Presenter'
'..\Core\Object Arts\Dolphin\MVP\Models\List\Dolphin List Models'
'..\Core\Object Arts\Dolphin\MVP\Presenters\List\Dolphin List Presenter'
'..\Core\Object Arts\Dolphin\Base\Dolphin Message Box'
'..\Core\Object Arts\Dolphin\MVP\Base\Dolphin MVP Base'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Radio\Dolphin Radio Buttons'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Text\Dolphin Text Presenter'
'..\Core\Object Arts\Dolphin\MVP\Type Converters\Dolphin Type Converters'
'..\Core\Object Arts\Dolphin\MVP\Models\Value\Dolphin Value Models'
'Jade UI'
'Jade UI Base'
'..\Core\Contributions\Solutions Software\SSW EditableListView').

package!

"Class Definitions"!

Object subclass: #JadeGsMethodShape
instanceVariableNames: 'ownerClass methodName source replacementSource isInstanceMethod packageName applied'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePreferenceObject subclass: #JadeRewriteToolPreference
instanceVariableNames: 'formatterClass'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteChangesBrowser
instanceVariableNames: 'changedMethodsPresenter differencePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteMethodsList
instanceVariableNames: 'methodsPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteTool
instanceVariableNames: 'searchTextPresenter replaceTextPresenter isMethodPresenter candidatesMethodsList scopeRadioPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsList subclass: #JadeRewriteReplaceMethodsList
instanceVariableNames: 'differencePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsList subclass: #JadeRewriteSearchMethodsList
instanceVariableNames: 'sourcePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeShell subclass: #JadeRewriteMethodsListShell
instanceVariableNames: 'rewriteMethodsListPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsListShell subclass: #JadeRewriteReplaceMethodsListShell
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsListShell subclass: #JadeRewriteSearchMethodsListShell
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!

"Global Aliases"!


"Loose Methods"!

"End of package definition"!

| package |
package := Package name: 'Jade Rewrite tool'.
package paxVersion: 1;
basicComment: ''.

package basicScriptAt: #postinstall put: 'JadeRewriteToolPreference default formatterClass: ''RBFormatter''.'.

package classNames
add: #JadeGsMethodShape;
add: #JadeRewriteChangesBrowser;
add: #JadeRewriteMethodsList;
add: #JadeRewriteMethodsListShell;
add: #JadeRewriteReplaceMethodsList;
add: #JadeRewriteReplaceMethodsListShell;
add: #JadeRewriteSearchMethodsList;
add: #JadeRewriteSearchMethodsListShell;
add: #JadeRewriteTool;
add: #JadeRewriteToolPreference;
yourself.

package binaryGlobalNames: (Set new
yourself).

package globalAliases: (Set new
yourself).

package setPrerequisites: #(
'..\Core\Object Arts\Dolphin\IDE\Base\Development System'
'..\Core\Object Arts\Dolphin\Base\Dolphin'
'..\Core\Object Arts\Dolphin\MVP\Base\Dolphin Basic Geometry'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Boolean\Dolphin Boolean Presenter'
'..\Core\Object Arts\Dolphin\MVP\Views\Common Controls\Dolphin Common Controls'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Difference\Dolphin Differences Presenter'
'..\Core\Object Arts\Dolphin\MVP\Models\List\Dolphin List Models'
'..\Core\Object Arts\Dolphin\MVP\Presenters\List\Dolphin List Presenter'
'..\Core\Object Arts\Dolphin\Base\Dolphin Message Box'
'..\Core\Object Arts\Dolphin\MVP\Base\Dolphin MVP Base'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Radio\Dolphin Radio Buttons'
'..\Core\Object Arts\Dolphin\MVP\Presenters\Text\Dolphin Text Presenter'
'..\Core\Object Arts\Dolphin\MVP\Type Converters\Dolphin Type Converters'
'..\Core\Object Arts\Dolphin\MVP\Models\Value\Dolphin Value Models'
'Jade UI'
'Jade UI Base'
'..\Core\Contributions\Solutions Software\SSW EditableListView').

package!

"Class Definitions"!

Object subclass: #JadeGsMethodShape
instanceVariableNames: 'ownerClass methodName source replacementSource isInstanceMethod packageName applied'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePreferenceObject subclass: #JadeRewriteToolPreference
instanceVariableNames: 'formatterClass'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteChangesBrowser
instanceVariableNames: 'changedMethodsPresenter differencePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteMethodsList
instanceVariableNames: 'methodsPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadePresenter subclass: #JadeRewriteTool
instanceVariableNames: 'searchTextPresenter replaceTextPresenter isMethodPresenter candidatesMethodsList scopeRadioPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsList subclass: #JadeRewriteReplaceMethodsList
instanceVariableNames: 'differencePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsList subclass: #JadeRewriteSearchMethodsList
instanceVariableNames: 'sourcePresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeShell subclass: #JadeRewriteMethodsListShell
instanceVariableNames: 'rewriteMethodsListPresenter'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsListShell subclass: #JadeRewriteReplaceMethodsListShell
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeRewriteMethodsListShell subclass: #JadeRewriteSearchMethodsListShell
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!

"Global Aliases"!


"Loose Methods"!

"End of package definition"!

148 changes: 74 additions & 74 deletions sources/JadeGsMethodShape.cls
Original file line number Diff line number Diff line change
@@ -1,109 +1,109 @@
"Filed out from Dolphin Smalltalk 7"!

Object subclass: #JadeGsMethodShape
instanceVariableNames: 'ownerClass methodName source replacementSource isInstanceMethod packageName applied'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeGsMethodShape guid: (GUID fromString: '{1aa1fb1a-ff88-4de6-ba91-71450fbb3ec6}')!
JadeGsMethodShape comment: ''!
!JadeGsMethodShape categoriesForClass!Unclassified! !
!JadeGsMethodShape methodsFor!

"Filed out from Dolphin Smalltalk 7"!

Object subclass: #JadeGsMethodShape
instanceVariableNames: 'ownerClass methodName source replacementSource isInstanceMethod packageName applied'
classVariableNames: ''
poolDictionaries: ''
classInstanceVariableNames: ''!
JadeGsMethodShape guid: (GUID fromString: '{1aa1fb1a-ff88-4de6-ba91-71450fbb3ec6}')!
JadeGsMethodShape comment: ''!
!JadeGsMethodShape categoriesForClass!Unclassified! !
!JadeGsMethodShape methodsFor!

applied
^applied!

^applied!

applied: anObject
applied := anObject!

applied := anObject!

apply

applied := true.!

applied := true.!

beClassMethod

isInstanceMethod := false!

isInstanceMethod := false!

initialize

super initialize.

isInstanceMethod := true.
applied := false.!

applied := false.!

isInstanceMethod
^isInstanceMethod!

^isInstanceMethod!

isInstanceMethod: anObject
isInstanceMethod := anObject!

isInstanceMethod := anObject!

methodName
^methodName!

^methodName!

methodName: anObject
methodName := anObject!

methodName := anObject!

ownerClass
^ownerClass!

^ownerClass!

ownerClass: anObject
ownerClass := anObject!

ownerClass := anObject!

packageName
^packageName!

^packageName!

packageName: anObject
packageName := anObject!

packageName := anObject!

printClass

^isInstanceMethod ifTrue: [ownerClass] ifFalse: [ownerClass , ' class']!

^isInstanceMethod ifTrue: [ownerClass] ifFalse: [ownerClass , ' class']!

printOn: target

super printOn: target.

target nextPutAll: '(', self printClass, '>>', methodName, ')'!

target nextPutAll: '(', self printClass, '>>', methodName, ')'!

replacementSource
^replacementSource!

^replacementSource!

replacementSource: anObject
replacementSource := anObject!

replacementSource := anObject!

source
^source!

^source!

source: anObject
source := anObject! !
!JadeGsMethodShape categoriesFor: #applied!accessing!private! !
!JadeGsMethodShape categoriesFor: #applied:!accessing!private! !
!JadeGsMethodShape categoriesFor: #apply!public! !
!JadeGsMethodShape categoriesFor: #beClassMethod!public! !
!JadeGsMethodShape categoriesFor: #initialize!public! !
!JadeGsMethodShape categoriesFor: #isInstanceMethod!accessing!private! !
!JadeGsMethodShape categoriesFor: #isInstanceMethod:!accessing!private! !
!JadeGsMethodShape categoriesFor: #methodName!accessing!private! !
!JadeGsMethodShape categoriesFor: #methodName:!accessing!private! !
!JadeGsMethodShape categoriesFor: #ownerClass!accessing!private! !
!JadeGsMethodShape categoriesFor: #ownerClass:!accessing!private! !
!JadeGsMethodShape categoriesFor: #packageName!accessing!private! !
!JadeGsMethodShape categoriesFor: #packageName:!accessing!private! !
!JadeGsMethodShape categoriesFor: #printClass!public! !
!JadeGsMethodShape categoriesFor: #printOn:!public! !
!JadeGsMethodShape categoriesFor: #replacementSource!accessing!private! !
!JadeGsMethodShape categoriesFor: #replacementSource:!accessing!private! !
!JadeGsMethodShape categoriesFor: #source!accessing!private! !
!JadeGsMethodShape categoriesFor: #source:!accessing!private! !

!JadeGsMethodShape class methodsFor!

source := anObject! !
!JadeGsMethodShape categoriesFor: #applied!accessing!private! !
!JadeGsMethodShape categoriesFor: #applied:!accessing!private! !
!JadeGsMethodShape categoriesFor: #apply!public! !
!JadeGsMethodShape categoriesFor: #beClassMethod!public! !
!JadeGsMethodShape categoriesFor: #initialize!public! !
!JadeGsMethodShape categoriesFor: #isInstanceMethod!accessing!private! !
!JadeGsMethodShape categoriesFor: #isInstanceMethod:!accessing!private! !
!JadeGsMethodShape categoriesFor: #methodName!accessing!private! !
!JadeGsMethodShape categoriesFor: #methodName:!accessing!private! !
!JadeGsMethodShape categoriesFor: #ownerClass!accessing!private! !
!JadeGsMethodShape categoriesFor: #ownerClass:!accessing!private! !
!JadeGsMethodShape categoriesFor: #packageName!accessing!private! !
!JadeGsMethodShape categoriesFor: #packageName:!accessing!private! !
!JadeGsMethodShape categoriesFor: #printClass!public! !
!JadeGsMethodShape categoriesFor: #printOn:!public! !
!JadeGsMethodShape categoriesFor: #replacementSource!accessing!private! !
!JadeGsMethodShape categoriesFor: #replacementSource:!accessing!private! !
!JadeGsMethodShape categoriesFor: #source!accessing!private! !
!JadeGsMethodShape categoriesFor: #source:!accessing!private! !

!JadeGsMethodShape class methodsFor!

newFor: className methodName: methodName source: source

^super new initialize
ownerClass: className;
methodName: methodName;
source: source;
yourself! !
!JadeGsMethodShape class categoriesFor: #newFor:methodName:source:!public! !

yourself! !
!JadeGsMethodShape class categoriesFor: #newFor:methodName:source:!public! !

Loading

0 comments on commit 6ecc3cd

Please sign in to comment.