work in progress - rewriting code generators to replace CustomSourceCodeBuilder, but RBClass, RBMetaclass, RBNamespace and CodeGenerator
authorJakub Nesveda <jakubnesveda@seznam.cz>
Sat, 20 Sep 2014 19:05:41 +0200
changeset 674 58df305d9184
parent 673 4d43ec4743cd
child 675 ac7b89fbd07c
child 676 669ed47b353e
work in progress - rewriting code generators to replace CustomSourceCodeBuilder, but RBClass, RBMetaclass, RBNamespace and CodeGenerator move CodeGenerator extensions from CustomSourceCodeBuilder to CustomSourceCodeGenerator refactor access generators to use CustomSourceCodeGenerator for method source generation
CustomChangeNotificationSetterMethodsCodeGenerator.st
CustomCodeGeneratorOrRefactoring.st
CustomCodeGeneratorOrRefactoringTestCase.st
CustomDefaultGetterMethodsCodeGenerator.st
CustomLazyInitializationGetterMethodsCodeGenerator.st
CustomSimpleGetterMethodsCodeGenerator.st
CustomSimpleSetterMethodsCodeGenerator.st
CustomSourceCodeGenerator.st
CustomSourceCodeGeneratorTests.st
CustomTestCaseSetUpCodeGenerator.st
CustomTestCaseTearDownCodeGenerator.st
CustomValueHolderGetterMethodsCodeGenerator.st
CustomValueHolderWithChangeNotificationGetterMethodsCodeGenerator.st
CustomValueHolderWithChangeNotificationSetterMethodsCodeGenerator.st
Make.proto
Make.spec
abbrev.stc
bc.mak
jn_refactoring_custom.st
libInit.cc
refactoring_custom.rc
--- a/CustomChangeNotificationSetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomChangeNotificationSetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -44,7 +44,7 @@
 sourceForClass: aClass variableName: aName
     "Returns setter method with change notification for given class and variable name"
 
-    | methodName comment methodBuilder argName |
+    | methodName comment argName |
 
     methodName := self methodNameFor: aName.
     argName := self argNameForMethodName: methodName.  
@@ -58,8 +58,7 @@
         comment := comment bindWith: varType with: aName.
     ].
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -71,10 +70,9 @@
         replace: '`argName' with: argName asString;
         replace: '`variableName' with: aName asString;
         replace: '`#variableName' with: ($#, aName asSymbol);
-        replace: '`"comment' with: comment.
+        replace: '`"comment' with: comment;
+        newSource.
 
-    ^ methodBuilder buildedSource
-
-    "Modified: / 06-07-2014 / 14:03:36 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:16:18 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- a/CustomCodeGeneratorOrRefactoring.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomCodeGeneratorOrRefactoring.st	Sat Sep 20 19:05:41 2014 +0200
@@ -3,7 +3,7 @@
 Object subclass:#CustomCodeGeneratorOrRefactoring
 	instanceVariableNames:'compositeChangeCollector compositeChangeNesting userPreferences
 		confirmChanges generateComments dialog changeManager codeBuilder
-		refactoryBuilder'
+		refactoryBuilder formatter'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-Refactoring-Custom'
@@ -189,6 +189,20 @@
     "Created: / 11-05-2014 / 00:27:49 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
+formatter
+
+    ^ formatter
+
+    "Created: / 19-09-2014 / 22:18:33 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+formatter: aSourceCodeFormatter
+
+    formatter := aSourceCodeFormatter
+
+    "Created: / 19-09-2014 / 22:18:50 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
 refactoryBuilder
 
     ^ refactoryBuilder
@@ -203,6 +217,18 @@
     "Modified (format): / 23-08-2014 / 00:14:33 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
+sourceCodeGenerator    
+    "Returns initialized source code generator"
+    | sourceCodeGenerator |
+
+    sourceCodeGenerator := CustomSourceCodeGenerator new.
+    sourceCodeGenerator formatter: formatter.
+    ^ sourceCodeGenerator.
+
+    "Created: / 19-09-2014 / 20:56:22 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:11:02 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
 userPreferences
 
     ^ userPreferences
@@ -390,13 +416,14 @@
     userPreferences := UserPreferences current.
     generateComments := userPreferences generateComments.
 
+    self setUpFormatter.
     self setUpCodeBuilder.
     self setUpRefactoryBuilder.
     self setUpDialog.
     self setUpChangeManager
 
     "Created: / 17-03-2014 / 22:27:32 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified: / 17-09-2014 / 22:43:54 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 18-09-2014 / 23:12:42 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
 setUpChangeManager
@@ -421,6 +448,13 @@
     "Created: / 09-06-2014 / 22:57:08 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
+setUpFormatter
+
+    formatter := CustomRBLocalSourceCodeFormatter new
+
+    "Created: / 18-09-2014 / 23:12:42 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
 setUpRefactoryBuilder
 
     refactoryBuilder := CustomRefactoryBuilder new.
--- a/CustomCodeGeneratorOrRefactoringTestCase.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomCodeGeneratorOrRefactoringTestCase.st	Sat Sep 20 19:05:41 2014 +0200
@@ -205,14 +205,14 @@
     self defaultUserPreferences.
     generatorOrRefactoring := self generatorOrRefactoring.
 
+    self setUpTestFormatter. 
+
     generatorOrRefactoring isNil ifFalse: [
         self setUpGeneratorOrRefactoring: generatorOrRefactoring
     ].
 
-    self setUpTestFormatter
-
     "Created: / 27-05-2014 / 19:16:44 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified: / 28-08-2014 / 23:29:46 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:29:54 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
 setUpBuilders
@@ -228,12 +228,14 @@
 
 setUpGeneratorOrRefactoring: aGeneratorOrRefactoring
 
+    aGeneratorOrRefactoring formatter: formatter.
     aGeneratorOrRefactoring codeBuilder: codeBuilder.
     aGeneratorOrRefactoring refactoryBuilder: refactoryBuilder.
     aGeneratorOrRefactoring changeManager: changeManager.
     aGeneratorOrRefactoring userPreferences: userPreferences
 
     "Created: / 23-08-2014 / 15:59:58 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:30:25 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
 setUpTestFormatter
--- a/CustomDefaultGetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomDefaultGetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -41,7 +41,7 @@
 sourceForClass: aClass variableName: aName
     "Returns getter method source code for default variable value"
 
-    | comment methodBuilder |
+    | comment |
 
     comment := ''.
 
@@ -50,19 +50,18 @@
         comment := comment bindWith: aName.
     ].
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
             self shouldImplement.
             ^ nil';
         replace: '`@methodName' with: (self defaultMethodNameFor: aName) asSymbol;
-        replace: '`"comment' with: comment.
-
-    ^ methodBuilder buildedSource
+        replace: '`"comment' with: comment;
+        newSource.
 
     "Created: / 30-06-2014 / 10:49:03 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:34:45 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
 !CustomDefaultGetterMethodsCodeGenerator methodsFor:'protected'!
--- a/CustomLazyInitializationGetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomLazyInitializationGetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -45,7 +45,7 @@
 sourceForClass: aClass variableName: aName
     "Returns getter with lazy initialization method source code for given class and variable name"
 
-    | methodName comment methodBuilder |
+    | methodName comment |
 
     methodName := self methodNameFor: aName.
     comment := ''.
@@ -58,8 +58,7 @@
         comment := comment bindWith: varType with: aName.
     ].
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -70,12 +69,11 @@
         replace: '`@methodName' with: methodName asSymbol;
         replace: '`@defaultMethodName' with: (self defaultMethodNameFor: aName) asSymbol;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
-
-    ^ methodBuilder buildedSource
+        replace: '`"comment' with: comment;
+        newSource.
 
     "Created: / 24-06-2014 / 23:24:41 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified: / 29-06-2014 / 23:30:27 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:35:12 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
 !CustomLazyInitializationGetterMethodsCodeGenerator methodsFor:'executing'!
--- a/CustomSimpleGetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomSimpleGetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -41,7 +41,7 @@
 sourceForClass: aClass variableName: aName
     "Returns simple getter method source code for given class and variable name"
 
-    | methodName comment methodBuilder |
+    | methodName comment |
 
     methodName := self methodNameFor: aName.
     comment := ''.
@@ -54,19 +54,17 @@
         comment := comment bindWith: varType with: aName.
     ].  
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
         `"comment
 
         ^ `variableName';
         replace: '`@methodName' with: methodName asSymbol;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
-
-    ^ methodBuilder buildedSource
+        replace: '`"comment' with: comment;
+        newSource.
 
     "Created: / 19-05-2014 / 20:32:34 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified: / 29-06-2014 / 21:36:03 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:35:39 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- a/CustomSimpleSetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomSimpleSetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -44,7 +44,7 @@
 sourceForClass: aClass variableName: aName
     "Returns simple setter for given class and variable name."
 
-    | methodName comment methodBuilder argName |
+    | methodName comment argName |
 
     methodName := self methodNameFor: aName.
     argName := self argNameForMethodName: methodName.  
@@ -58,8 +58,7 @@
         comment := comment bindWith: varType with: aName.
     ].
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -67,10 +66,9 @@
         replace: '`@methodName' with: (methodName, ': ', argName) asSymbol;
         replace: '`argName' with: argName asString;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
+        replace: '`"comment' with: comment;
+        newSource.
 
-    ^ methodBuilder buildedSource
-
-    "Modified: / 05-07-2014 / 19:37:43 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:36:17 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CustomSourceCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -0,0 +1,181 @@
+"{ Package: 'jn:refactoring_custom' }"
+
+CodeGenerator subclass:#CustomSourceCodeGenerator
+	instanceVariableNames:'formatter commentPlaceholderMarker commentReplacements'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Refactoring-Custom'
+!
+
+!CustomSourceCodeGenerator class methodsFor:'documentation'!
+
+documentation
+"
+    Extension for CodeGenerator to support work just with source code and with formatter.
+    It would be nice to do it just as extension, but I dont know how to add instance variable as extension.
+
+    [author:]
+        Jakub Nesveda <nesvejak@fit.cvut.cz>
+
+"
+! !
+
+!CustomSourceCodeGenerator methodsFor:'accessing'!
+
+commentPlaceholderMarker: aString
+    "
+    Sets prefix string which will mark comment replace 
+    in code replacements given by:
+    replace: '`comment' with: 'comment'
+    "
+
+    commentPlaceholderMarker := aString
+
+    "Created: / 19-09-2014 / 21:17:08 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+formatter
+
+    ^ formatter
+
+    "Created: / 19-09-2014 / 22:24:21 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+formatter: aSourceCodeFormatter
+
+    formatter := aSourceCodeFormatter
+
+    "Created: / 19-09-2014 / 22:25:13 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+newSource
+    "
+    Returns formatted method source
+    code as string (with replacements and so on)
+    "
+
+    | parser method |  
+
+    source := self replaceCommentsInSource: source.
+    parser := RBParser new.
+    recordedReplacementsInSource := OrderedCollection new.
+    parser errorBlock:[ :str :pos | self error: ('Error: %1: %2' bindWith: pos with: str). ^ self ].
+
+    parser initializeParserWith: source type: #rewriteSavingCommentsOn:errorBlock:.
+    method := parser parseMethod: source.    
+
+    method source: nil.
+    method acceptVisitor: self.
+    self replaceInSourceCode.
+    method source: source.
+
+    ^ formatter formatParseTree: method.
+
+    "Created: / 19-09-2014 / 22:07:14 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+replace: placeholder with: code
+
+    (placeholder startsWith: commentPlaceholderMarker) ifTrue: [
+        commentReplacements
+            at: placeholder 
+            put: code
+    ]
+    ifFalse: [
+        replacements 
+            at: placeholder
+            put: (self replacementFromCode: code)
+    ]
+
+    "Created: / 19-09-2014 / 21:18:30 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 23:58:39 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+! !
+
+!CustomSourceCodeGenerator methodsFor:'initialization'!
+
+initialize
+    "Invoked when a new instance is created."
+
+    super initialize.
+    commentPlaceholderMarker := '`"'.
+    commentReplacements := Dictionary new.
+
+    "Created: / 19-09-2014 / 21:42:26 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+! !
+
+!CustomSourceCodeGenerator methodsFor:'private'!
+
+formatReplacement: replacement 
+    "Returns formatted source code replacement, but keep Symbol not formatted"
+
+    replacement isSymbol ifTrue: [ 
+        ^ replacement formattedCode
+    ].
+
+    ^ formatter formatParseTree: replacement
+
+    "Created: / 20-09-2014 / 10:01:18 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+replaceCommentsInSource: aSourceCodeString
+    "
+    Returns source string with replaced occurences of comment
+    replaces given by:
+    replace: '`{double_quote_char}comment' with: '{double_quote_char}a comment{double_quote_char}'
+    where {double_quote_char} is "" (but not escaped like in this comment)
+    "
+
+    | sourceCode |
+
+    sourceCode := aSourceCodeString.
+
+    commentReplacements keysAndValuesDo: [ :placeholder :code | 
+        sourceCode := sourceCode copyReplaceString: placeholder withString: code       
+    ].
+
+    ^ sourceCode
+
+    "Created: / 19-09-2014 / 22:08:09 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+replacePlaceholdersInSelectorPartsOf:aMessageNode 
+    aMessageNode selectorParts do:[:part | 
+        part isPatternVariable ifTrue:[
+            |replacement|
+
+            replacement := self replacementFor:part value.
+            "(replacement isSymbol or:[ replacement isVariable ]) ifFalse:[
+                self error:'Replacement for selector parts must be a single selector'
+            ]."
+            replacement isNil ifTrue: [ 
+                self error: 'None replacement for: ', part value asString.
+            ].
+            source notNil ifTrue:[
+                self 
+                      recordReplaceInSourceFrom:part start
+                      to:part stop
+                      by: (self formatReplacement: replacement).
+            ].
+            part value: (self formatReplacement: replacement).
+        ]
+    ]
+
+    "Created: / 19-09-2014 / 23:55:53 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 20-09-2014 / 10:14:59 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+replacementFromCode: aCode
+
+    ^ aCode isSymbol 
+        ifTrue:[aCode]
+        ifFalse:[
+            RBParser parseRewriteExpression: aCode onError: [ :str :pos |
+                RBParser parseRewriteMethod: aCode onError: [ :str :pos | 
+                    self error: 'Cannot parse: ', str, ' at pos: ', pos asString 
+                ]
+            ]
+        ]
+
+    "Created: / 19-09-2014 / 23:56:27 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CustomSourceCodeGeneratorTests.st	Sat Sep 20 19:05:41 2014 +0200
@@ -0,0 +1,128 @@
+"{ Package: 'jn:refactoring_custom' }"
+
+TestCase subclass:#CustomSourceCodeGeneratorTests
+	instanceVariableNames:'sourceCodeGenerator'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Refactoring-Custom-Tests'
+!
+
+!CustomSourceCodeGeneratorTests methodsFor:'initialization & release'!
+
+setUp
+
+    sourceCodeGenerator := CustomSourceCodeGenerator new.
+    sourceCodeGenerator formatter: CustomNoneSourceCodeFormatter new.
+
+    "Modified: / 19-09-2014 / 23:42:00 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+! !
+
+!CustomSourceCodeGeneratorTests methodsFor:'tests'!
+
+test_new_source_literal_replacement
+    |expectedSource actualSource|
+
+    actualSource := sourceCodeGenerator
+            replace:'`"comment1' with:'"comment1"';
+            replace:'`"comment2' with:'"other comment2"';
+            replace:'`#literal' with:'''some info''';
+            source:'selector
+    `"comment1
+
+    self information: `#literal.
+
+    `"comment2
+
+    ^ 55';
+            newSource.
+    expectedSource := 'selector
+    "comment1"
+
+    self information: ''some info''.
+
+    "other comment2"
+
+    ^ 55'.
+    self assert:expectedSource = actualSource.
+
+    "Created: / 19-09-2014 / 23:45:30 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+test_new_source_selector_as_symbol
+    | expectedSource actualSource |
+
+    actualSource := sourceCodeGenerator
+        source: '`@selector
+            self shouldImplement';
+        replace: '`@selector' with: 'aSelector: withParam' asSymbol;
+        newSource.    
+
+    expectedSource := 'aSelector: withParam
+            self shouldImplement'.
+
+    self assert: expectedSource = actualSource.
+
+    "Created: / 20-09-2014 / 09:36:39 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+test_new_source_selector_replacement
+    |expectedSource actualSource|
+
+    actualSource := sourceCodeGenerator
+            source:'`@selector
+            self shouldImplement';
+            replace:'`@selector' with:'aSelector';
+            newSource.
+    expectedSource := 'aSelector
+            self shouldImplement'.
+    self assert:expectedSource = actualSource.
+
+    "Created: / 19-09-2014 / 23:51:19 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+test_new_source_selector_with_param
+    | expectedSource actualSource |
+
+    actualSource := sourceCodeGenerator
+        source: '`@selector
+            self shouldImplement';
+        replace: '`@selector' with: 'aSelector: withParam';
+        newSource.    
+
+    expectedSource := 'aSelector: withParam
+            self shouldImplement'.
+
+    self assert: expectedSource = actualSource.
+
+    "Created: / 20-09-2014 / 09:39:15 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+!
+
+test_replace_comments_in_source
+    | expectedSource actualSource |
+
+    actualSource := sourceCodeGenerator
+        replace: '`"comment1' with: '"comment1"'; 
+        replace: '`"comment2' with: '"other comment2"';
+        replaceCommentsInSource:'selector
+    `"comment1
+
+    self information: ''some info''.
+
+    `"comment2
+
+    ^ 55'.    
+
+    expectedSource := 'selector
+    "comment1"
+
+    self information: ''some info''.
+
+    "other comment2"
+
+    ^ 55'.
+    
+    self assert: expectedSource = actualSource.
+
+    "Created: / 19-09-2014 / 22:50:29 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+! !
+
--- a/CustomTestCaseSetUpCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomTestCaseSetUpCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -73,12 +73,13 @@
         category := (TestCase compiledMethodAt: #setUp) category.
     ].
 
-    builder createMethod
+    codeBuilder createMethod
         class: class;
         source: source;
         category: category.
 
     "Created: / 05-08-2014 / 14:17:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-09-2014 / 18:29:05 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
 buildInContext:aCustomContext
--- a/CustomTestCaseTearDownCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomTestCaseTearDownCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -73,12 +73,13 @@
         category := (TestCase compiledMethodAt: #tearDown ) category.
     ].
 
-    builder createMethod
+    codeBuilder createMethod
         class: class;
         source: source;
         category: category.
 
     "Created: / 05-08-2014 / 14:17:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-09-2014 / 18:48:43 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 !
 
 buildInContext:aCustomContext
--- a/CustomValueHolderGetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomValueHolderGetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -52,7 +52,7 @@
 sourceForClass: aClass variableName: aName
     "Returns getter method source code with ValueHolder for given class and variable name"
 
-    | methodName comment methodBuilder |
+    | methodName comment |
 
     methodName := self methodNameFor: aName.
     comment := ''.
@@ -62,8 +62,7 @@
         comment := comment bindWith: aName.
     ].  
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -73,12 +72,10 @@
             ^ `variableName';
         replace: '`@methodName' with: methodName asSymbol;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
-
-    ^ methodBuilder buildedSource
+        replace: '`"comment' with: comment;
+        newSource.
 
     "Created: / 19-05-2014 / 20:52:07 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified: / 29-06-2014 / 21:39:48 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-    "Modified (comment): / 30-06-2014 / 19:19:23 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:36:39 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- a/CustomValueHolderWithChangeNotificationGetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomValueHolderWithChangeNotificationGetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -51,7 +51,7 @@
 sourceForClass: aClass variableName: aName
     "Returns getter method source code with ValueHolder and change notification for given class and variable name"
 
-    | methodName comment methodBuilder |
+    | methodName comment |
 
     methodName := self methodNameFor: aName.
     comment := ''.
@@ -61,8 +61,7 @@
         comment := comment bindWith: aName.
     ].  
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -73,10 +72,10 @@
             ^ `variableName';
         replace: '`@methodName' with: methodName asSymbol;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
-
-    ^ methodBuilder buildedSource
+        replace: '`"comment' with: comment;
+        newSource.
 
     "Created: / 30-06-2014 / 19:18:35 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:37:00 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- a/CustomValueHolderWithChangeNotificationSetterMethodsCodeGenerator.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/CustomValueHolderWithChangeNotificationSetterMethodsCodeGenerator.st	Sat Sep 20 19:05:41 2014 +0200
@@ -44,7 +44,7 @@
 sourceForClass: aClass variableName: aName
     "Returns setter method for ValueHolder with change notification for given class and variable name"
 
-    | methodName comment methodBuilder argName |
+    | methodName comment argName |
 
     methodName := self methodNameFor: aName.
     argName := self argNameForMethodName: methodName.  
@@ -55,8 +55,7 @@
         comment := comment bindWith: aName.
     ].
 
-    methodBuilder := codeBuilder methodBuilder.
-    methodBuilder
+    ^ self sourceCodeGenerator
         source: '`@methodName
             `"comment
 
@@ -77,10 +76,9 @@
         replace: '`@methodName' with: (methodName, ': ', argName) asSymbol;
         replace: '`argName' with: argName asString;
         replace: '`variableName' with: aName asString;
-        replace: '`"comment' with: comment.
+        replace: '`"comment' with: comment;
+        newSource.
 
-    ^ methodBuilder buildedSource
-
-    "Modified: / 06-07-2014 / 23:54:51 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
+    "Modified: / 19-09-2014 / 22:37:19 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
 ! !
 
--- a/Make.proto	Wed Sep 17 23:01:25 2014 +0200
+++ b/Make.proto	Sat Sep 20 19:05:41 2014 +0200
@@ -147,6 +147,7 @@
 $(OUTDIR)CustomRefactoryBuilder.$(O) CustomRefactoryBuilder.$(H): CustomRefactoryBuilder.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/refactoring/RefactoryBuilder.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeBuilder.$(O) CustomSourceCodeBuilder.$(H): CustomSourceCodeBuilder.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/AddClassChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/AddMethodChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/InteractiveAddClassChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/InteractiveAddMethodChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/RefactoryChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/RefactoryClassChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser/RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libtool/CodeGenerator.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeFormatter.$(O) CustomSourceCodeFormatter.$(H): CustomSourceCodeFormatter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CustomSourceCodeGenerator.$(O) CustomSourceCodeGenerator.$(H): CustomSourceCodeGenerator.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser/RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libtool/CodeGenerator.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeSelection.$(O) CustomSourceCodeSelection.$(H): CustomSourceCodeSelection.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TestClass.$(O) TestClass.$(H): TestClass.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TestClass2.$(O) TestClass2.$(H): TestClass2.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Wed Sep 17 23:01:25 2014 +0200
+++ b/Make.spec	Sat Sep 20 19:05:41 2014 +0200
@@ -63,6 +63,7 @@
 	CustomRefactoryBuilder \
 	CustomSourceCodeBuilder \
 	CustomSourceCodeFormatter \
+	CustomSourceCodeGenerator \
 	CustomSourceCodeSelection \
 	TestClass \
 	TestClass2 \
@@ -123,6 +124,7 @@
     $(OUTDIR_SLASH)CustomRefactoryBuilder.$(O) \
     $(OUTDIR_SLASH)CustomSourceCodeBuilder.$(O) \
     $(OUTDIR_SLASH)CustomSourceCodeFormatter.$(O) \
+    $(OUTDIR_SLASH)CustomSourceCodeGenerator.$(O) \
     $(OUTDIR_SLASH)CustomSourceCodeSelection.$(O) \
     $(OUTDIR_SLASH)TestClass.$(O) \
     $(OUTDIR_SLASH)TestClass2.$(O) \
--- a/abbrev.stc	Wed Sep 17 23:01:25 2014 +0200
+++ b/abbrev.stc	Sat Sep 20 19:05:41 2014 +0200
@@ -21,6 +21,8 @@
 CustomRefactoryBuilder CustomRefactoryBuilder jn:refactoring_custom 'Interface-Refactoring-Custom' 0
 CustomSourceCodeBuilder CustomSourceCodeBuilder jn:refactoring_custom 'Interface-Refactoring-Custom' 0
 CustomSourceCodeFormatter CustomSourceCodeFormatter jn:refactoring_custom 'Interface-Refactoring-Custom' 0
+CustomSourceCodeGenerator CustomSourceCodeGenerator jn:refactoring_custom 'Interface-Refactoring-Custom' 0
+CustomSourceCodeGeneratorTests CustomSourceCodeGeneratorTests jn:refactoring_custom 'Interface-Refactoring-Custom-Tests' 1
 CustomSourceCodeSelection CustomSourceCodeSelection jn:refactoring_custom 'Interface-Refactoring-Custom' 0
 CustomSourceCodeSelectionTests CustomSourceCodeSelectionTests jn:refactoring_custom 'Interface-Refactoring-Custom-Tests' 1
 TestClass TestClass jn:refactoring_custom 'Interface-Refactoring-Custom' 1
--- a/bc.mak	Wed Sep 17 23:01:25 2014 +0200
+++ b/bc.mak	Sat Sep 20 19:05:41 2014 +0200
@@ -93,6 +93,7 @@
 $(OUTDIR)CustomRefactoryBuilder.$(O) CustomRefactoryBuilder.$(H): CustomRefactoryBuilder.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\refactoring\RefactoryBuilder.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeBuilder.$(O) CustomSourceCodeBuilder.$(H): CustomSourceCodeBuilder.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\AddClassChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\AddMethodChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\InteractiveAddClassChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\InteractiveAddMethodChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\RefactoryChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\RefactoryClassChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser\RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libtool\CodeGenerator.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeFormatter.$(O) CustomSourceCodeFormatter.$(H): CustomSourceCodeFormatter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CustomSourceCodeGenerator.$(O) CustomSourceCodeGenerator.$(H): CustomSourceCodeGenerator.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser\RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libtool\CodeGenerator.$(H) $(STCHDR)
 $(OUTDIR)CustomSourceCodeSelection.$(O) CustomSourceCodeSelection.$(H): CustomSourceCodeSelection.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TestClass.$(O) TestClass.$(H): TestClass.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TestClass2.$(O) TestClass2.$(H): TestClass2.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/jn_refactoring_custom.st	Wed Sep 17 23:01:25 2014 +0200
+++ b/jn_refactoring_custom.st	Sat Sep 20 19:05:41 2014 +0200
@@ -91,6 +91,8 @@
         CustomRefactoryBuilder
         CustomSourceCodeBuilder
         CustomSourceCodeFormatter
+        CustomSourceCodeGenerator
+        (CustomSourceCodeGeneratorTests autoload)
         CustomSourceCodeSelection
         (CustomSourceCodeSelectionTests autoload)
         TestClass
--- a/libInit.cc	Wed Sep 17 23:01:25 2014 +0200
+++ b/libInit.cc	Sat Sep 20 19:05:41 2014 +0200
@@ -40,6 +40,7 @@
 _CustomRefactoryBuilder_Init(pass,__pRT__,snd);
 _CustomSourceCodeBuilder_Init(pass,__pRT__,snd);
 _CustomSourceCodeFormatter_Init(pass,__pRT__,snd);
+_CustomSourceCodeGenerator_Init(pass,__pRT__,snd);
 _CustomSourceCodeSelection_Init(pass,__pRT__,snd);
 _TestClass_Init(pass,__pRT__,snd);
 _TestClass2_Init(pass,__pRT__,snd);
--- a/refactoring_custom.rc	Wed Sep 17 23:01:25 2014 +0200
+++ b/refactoring_custom.rc	Sat Sep 20 19:05:41 2014 +0200
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "My CopyRight or CopyLeft\0"
       VALUE "ProductName", "ProductName\0"
       VALUE "ProductVersion", "6.2.4.1333\0"
-      VALUE "ProductDate", "Wed, 17 Sep 2014 20:58:21 GMT\0"
+      VALUE "ProductDate", "Sat, 20 Sep 2014 16:50:03 GMT\0"
     END
 
   END