Fixes to write a package in Cypress format
authorjv
Thu, 30 Aug 2012 12:55:16 +0000
changeset 4 207b76be6bcd
parent 3 9a409f9edb67
child 5 0fd3156a3a9f
Fixes to write a package in Cypress format
CypressClassStructure.st
CypressMethodStructure.st
CypressPackageStructure.st
CypressPackageWriter.st
CypressStructure.st
cypress.rc
extensions.st
stx_goodies_cypress.st
--- a/CypressClassStructure.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/CypressClassStructure.st	Thu Aug 30 12:55:16 2012 +0000
@@ -196,39 +196,39 @@
         aStream 
                 tab: indent;
                 nextPutAll: '{';
-                newLine.
+                cr.
         indent := indent + 1.
         aStream
                 tab: indent;
                 nextPutAll: '"name"';
                 nextPutAll: ' : ';
                 nextPutAll: '"', self name, (self isClassExtension ifTrue: [ '.extension' ] ifFalse: [ '.class' ]), '",';
-                newLine.
+                cr.
         aStream
                 tab: indent;
                 nextPutAll: '"instance" : [';
-                newLine;
+                cr;
                 yourself.
         methods := self instanceMethods values asArray asSortedCollection: [:a :b | a selector <= b selector].
         1 to: methods size do: [:index | | methodStructure | 
                 methodStructure := methods at: index.
                 methodStructure writeJsonOn: aStream indent: indent + 1.
-                index < methods size ifTrue: [ aStream nextPutAll: ','; newLine ]].
+                index < methods size ifTrue: [ aStream nextPutAll: ','; cr ]].
         aStream
                 tab: indent;
                 nextPutAll: '],';
-                newLine;
+                cr;
                 yourself.
         aStream
                 tab: indent;
                 nextPutAll: '"class" : [';
-                newLine;
+                cr;
                 yourself.
         methods := self classMethods values asArray asSortedCollection: [:a :b | a selector <= b selector].
         1 to: methods size do: [:index | | methodStructure | 
                 methodStructure := methods at: index.
                 methodStructure writeJsonOn: aStream indent: indent + 1.
-                index < methods size ifTrue: [ aStream nextPutAll: ','; newLine ]].
+                index < methods size ifTrue: [ aStream nextPutAll: ','; cr ]].
         aStream
                 tab: indent;
                 nextPutAll: ']'.
@@ -236,25 +236,25 @@
                 ifFalse: [ 
                         aStream
                                 nextPutAll: ',';
-                                newLine;
+                                cr;
                                 tab: indent;
                                 nextPutAll: '"README.md" : ';
                                 yourself.
                         self comment writeCypressJsonOn: aStream forHtml: true indent: indent ].
         aStream
                 nextPutAll: ',';
-                newLine;
+                cr;
                 tab: indent;
                 nextPutAll: '"properties.json" : ';
                 yourself.
         self properties writeCypressJsonOn: aStream forHtml: true indent: indent.
         indent := indent - 1.
         aStream
-                newLine;
+                cr;
                 tab: indent;
                 nextPutAll: ' }'
 
-    "Modified: / 30-08-2012 / 13:31:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 30-08-2012 / 14:50:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressClassStructure class methodsFor:'documentation'!
--- a/CypressMethodStructure.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/CypressMethodStructure.st	Thu Aug 30 12:55:16 2012 +0000
@@ -42,13 +42,15 @@
 
 cypressSource
 
-	| stream |
-	stream := WriteStream on: String new.
-	stream 
-		nextPutAll: self category;
-		newLine;
-		nextPutAll: self source.
-	^stream contents
+        | stream |
+        stream := WriteStream on: String new.
+        stream 
+                nextPutAll: self category;
+                cr;
+                nextPutAll: self source.
+        ^stream contents
+
+    "Modified: / 30-08-2012 / 14:50:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 isMetaclass
@@ -165,29 +167,31 @@
 
 writeJsonOn: aStream  indent: startIndent
 
-	| indent |
-	indent := startIndent.
-	aStream 
-		tab: indent;
-		nextPutAll: '{';
-		newLine.
-	indent := indent + 1.
-	aStream
-		tab: indent;
-		nextPutAll: '"name"';
-		nextPutAll: ' : ';
-		nextPutAll: '"', self name, '.st",';
-		newLine.
-	aStream
-		tab: indent;
-		nextPutAll: '"contents"';
-		nextPutAll: ' : '.
-	self cypressSource writeCypressJsonOn: aStream forHtml: true indent: indent.
-	indent := indent - 1.
-	aStream
-		newLine;
-		tab: indent;
-		nextPutAll: ' }'
+        | indent |
+        indent := startIndent.
+        aStream 
+                tab: indent;
+                nextPutAll: '{';
+                cr.
+        indent := indent + 1.
+        aStream
+                tab: indent;
+                nextPutAll: '"name"';
+                nextPutAll: ' : ';
+                nextPutAll: '"', self name, '.st",';
+                cr.
+        aStream
+                tab: indent;
+                nextPutAll: '"contents"';
+                nextPutAll: ' : '.
+        self cypressSource writeCypressJsonOn: aStream forHtml: true indent: indent.
+        indent := indent - 1.
+        aStream
+                cr;
+                tab: indent;
+                nextPutAll: ' }'
+
+    "Modified: / 30-08-2012 / 14:49:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressMethodStructure class methodsFor:'documentation'!
--- a/CypressPackageStructure.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/CypressPackageStructure.st	Thu Aug 30 12:55:16 2012 +0000
@@ -77,46 +77,52 @@
 
 fromPackage: aCypressPackageDefinition
 
-	| snapshot classMap classDefinitions classStructure |
-	snapshot := aCypressPackageDefinition snapshot.
-	name := aCypressPackageDefinition name, '.package'.
-	properties := Dictionary new.
-	classDefinitions := Set new.
-	classMap := Dictionary new.
-	snapshot definitions do: [:definition |  
-			definition 
-				classDefinition: [:classDefinition |  classDefinitions add: classDefinition ] 
-				methodDefinition: [:methodDefinition | 
-					(classMap 
-						at: methodDefinition className 
-						ifAbsent: [classMap at: methodDefinition className put: Set new]) 
-							add: methodDefinition. ]].
-	classDefinitions do: [:classDefinition |
-		classStructure := (CypressClassStructure fromClassDefinition: classDefinition)
-			packageStructure: self.
-		(classMap removeKey: classDefinition className ifAbsent: [#()]) do: [:methodDefinition | | methodStructure |
-			methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
-				packageStructure: self;
-				classStructure: classStructure.
-			(methodDefinition
-				instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
-				classMethod: [:classMethod | classStructure classMethods ])
-					at: methodDefinition selector
-					put: methodStructure ].
-		self classes add: classStructure ].
-	classMap keysAndValuesDo: [:className :methods |
-		classStructure := (CypressClassStructure new name: className)
-			packageStructure: self.
-		methods do: [:methodDefinition | | methodStructure |
-			methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
-				packageStructure: self;
-				classStructure: classStructure.
-			(methodDefinition
-				instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
-				classMethod: [:classMethod | classStructure classMethods ])
-					at: methodDefinition selector
-					put: methodStructure ].
-		self extensions add: classStructure ].
+        | snapshot classMap classDefinitions classStructure |
+        snapshot := aCypressPackageDefinition snapshot.
+        name := (aCypressPackageDefinition name copy
+                    replaceAll: $: with:$_;
+                    replaceAll: $/ with:$_;
+                    yourself)
+                    , '.package'.
+        properties := Dictionary new.
+        classDefinitions := Set new.
+        classMap := Dictionary new.
+        snapshot definitions do: [:definition |  
+                        definition 
+                                classDefinition: [:classDefinition |  classDefinitions add: classDefinition ] 
+                                methodDefinition: [:methodDefinition | 
+                                        (classMap 
+                                                at: methodDefinition className 
+                                                ifAbsent: [classMap at: methodDefinition className put: Set new]) 
+                                                        add: methodDefinition. ]].
+        classDefinitions do: [:classDefinition |
+                classStructure := (CypressClassStructure fromClassDefinition: classDefinition)
+                        packageStructure: self.
+                (classMap removeKey: classDefinition className ifAbsent: [#()]) do: [:methodDefinition | | methodStructure |
+                        methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
+                                packageStructure: self;
+                                classStructure: classStructure.
+                        (methodDefinition
+                                instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
+                                classMethod: [:classMethod | classStructure classMethods ])
+                                        at: methodDefinition selector
+                                        put: methodStructure ].
+                self classes add: classStructure ].
+        classMap keysAndValuesDo: [:className :methods |
+                classStructure := (CypressClassStructure new name: className)
+                        packageStructure: self.
+                methods do: [:methodDefinition | | methodStructure |
+                        methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
+                                packageStructure: self;
+                                classStructure: classStructure.
+                        (methodDefinition
+                                instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
+                                classMethod: [:classMethod | classStructure classMethods ])
+                                        at: methodDefinition selector
+                                        put: methodStructure ].
+                self extensions add: classStructure ].
+
+    "Modified: / 30-08-2012 / 14:37:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressPackageStructure methodsFor:'snapshotting'!
@@ -144,45 +150,47 @@
 
 writeJsonOn: aStream  indent: startIndent
 
-	| indent |
-	indent := startIndent.
-	aStream 
-		tab: indent;
-		nextPutAll: '{';
-		newLine.
-	indent := indent + 1.
-	aStream
-		tab: indent;
-		nextPutAll: '"name"';
-		nextPutAll: ' : ';
-		nextPutAll: '"', self name, '",'.
-	aStream
-		newLine;
-		tab: indent;
-		nextPutAll: '"contents" : [';
-		newLine;
-		yourself.
-	1 to: self classes size do: [:index | | classStructure | 
-		classStructure := self classes at: index.
-		classStructure writeJsonOn: aStream indent: indent + 1.
-		(self extensions size > 0 or: [ index < self classes size]) ifTrue: [ aStream nextPutAll: ','; newLine. ]].
-	1 to: self extensions size do: [:index | | classStructure | 
-		classStructure := self extensions at: index.
-		classStructure writeJsonOn: aStream indent: indent + 1.
-		index < self extensions size ifTrue: [ aStream nextPutAll: ','; newLine.] ].
-	aStream
-		newLine;
-		tab: indent;
-		nextPutAll: '],';
-		newLine;
-		tab: indent;
-		nextPutAll: '"properties.json" : '.
-	self properties writeCypressJsonOn: aStream forHtml: true indent: indent.
-	indent := indent - 1.
-	aStream 
-		newLine;
-		tab: indent;
-		nextPutAll: '}'
+        | indent |
+        indent := startIndent.
+        aStream 
+                tab: indent;
+                nextPutAll: '{';
+                cr.
+        indent := indent + 1.
+        aStream
+                tab: indent;
+                nextPutAll: '"name"';
+                nextPutAll: ' : ';
+                nextPutAll: '"', self name, '",'.
+        aStream
+                cr;
+                tab: indent;
+                nextPutAll: '"contents" : [';
+                cr;
+                yourself.
+        1 to: self classes size do: [:index | | classStructure | 
+                classStructure := self classes at: index.
+                classStructure writeJsonOn: aStream indent: indent + 1.
+                (self extensions size > 0 or: [ index < self classes size]) ifTrue: [ aStream nextPutAll: ','; newLine. ]].
+        1 to: self extensions size do: [:index | | classStructure | 
+                classStructure := self extensions at: index.
+                classStructure writeJsonOn: aStream indent: indent + 1.
+                index < self extensions size ifTrue: [ aStream nextPutAll: ','; newLine.] ].
+        aStream
+                cr;
+                tab: indent;
+                nextPutAll: '],';
+                cr;
+                tab: indent;
+                nextPutAll: '"properties.json" : '.
+        self properties writeCypressJsonOn: aStream forHtml: true indent: indent.
+        indent := indent - 1.
+        aStream 
+                cr;
+                tab: indent;
+                nextPutAll: '}'
+
+    "Modified: / 30-08-2012 / 14:49:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressPackageStructure class methodsFor:'documentation'!
--- a/CypressPackageWriter.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/CypressPackageWriter.st	Thu Aug 30 12:55:16 2012 +0000
@@ -55,28 +55,31 @@
 
 !CypressPackageWriter class methodsFor:'services'!
 
-writeCodePackage: aCodePackage
-	"
-	For example:
-		CypressPackageWriter writeCodePackage: (CodePackage named: 'Cypress-Structure' createIfAbsent: true registerIfNew: false)
-		CypressPackageWriter writeCodePackage: (CodePackage named: 'Morphic' createIfAbsent: true registerIfNew: false)
-	"
-	CypressPackageWriter
-		writePackageStructure: 
-			(CypressPackageStructure fromPackage: 
-				(CypressPackageDefinition new name: aCodePackage packageName))
-		to: FileDirectory default
+writePackage: packageId to: directory
+    "Writes a given package to a directory in Cypress format"
+
+    CypressPackageWriter
+        writePackageStructure: 
+            (CypressPackageStructure fromPackage: 
+                (CypressPackageDefinition new name: packageId))
+        to: directory
+
+    "Created: / 30-08-2012 / 14:29:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressPackageWriter methodsFor:'accessing'!
 
 packageDirectory
 
-	packageDirectory 
-		ifNil: [ 
-			packageDirectory := self rootDirectory directoryNamed: self packageStructure name.
-			packageDirectory assureExistence ].
-	^packageDirectory
+    packageDirectory isNil ifTrue: [ 
+        packageDirectory := self rootDirectory asFilename / self packageStructure name.
+        packageDirectory exists ifFalse:[
+            packageDirectory recursiveMakeDirectory 
+        ]
+    ].
+    ^packageDirectory
+
+    "Modified: / 30-08-2012 / 14:38:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 packageDirectory: aPackageDirectory
@@ -107,12 +110,17 @@
 !CypressPackageWriter methodsFor:'private'!
 
 directoryForDirectoryNamed: directoryNameOrPath
-    ^ directoryNameOrPath = '.'
-        ifTrue: [ self packageDirectory assureExistence ]
-        ifFalse: [ | dir |
-            dir := self packageDirectory directoryNamed: directoryNameOrPath.
-            dir assureExistence.
-            dir  ]
+    | directory |
+
+    directoryNameOrPath = '.'
+        ifTrue: [ directory := self packageDirectory ]
+        ifFalse:[ directory := self packageDirectory / directoryNameOrPath ].
+    directory exists ifFalse:[
+        directory recursiveMakeDirectory
+    ].
+    ^directory
+
+    "Modified: / 30-08-2012 / 14:48:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileNameForSelector: selector
@@ -138,20 +146,24 @@
 writeInDirectoryName: directoryNameOrPath fileName: fileName extension: ext visit: visitBlock
     | directory |
     directory := self directoryForDirectoryNamed: directoryNameOrPath.
-    directory
-        forceNewFileNamed: fileName , ext
-        do: [ :file |
-            visitBlock value: file ]
+    (directory / (fileName , ext))
+        writingFileDo:[:file| 
+            visitBlock value: file 
+        ]
+
+    "Modified: / 30-08-2012 / 14:41:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressPackageWriter methodsFor:'writing'!
 
 write
 
-	self packageDirectory exists
-        ifTrue: [ self packageDirectory recursiveDelete ].
-    	self writePropertiesFile.
-	self writePackageStructure
+        self packageDirectory exists
+        ifTrue: [ self packageDirectory recursiveRemove. self packageDirectory makeDirectory ].
+        self writePropertiesFile.
+        self writePackageStructure
+
+    "Modified: / 30-08-2012 / 14:39:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 writeClassComment: classStructure on: fileStream
@@ -205,10 +217,12 @@
         fileName: filename
         extension: '.st'
         visit: [:fileStream |
-		fileStream
-        		nextPutAll: methodStructure category;
-        		newLine;
-        		nextPutAll: (methodStructure source withLineEndings: String lfString) ]
+                fileStream
+                        nextPutAll: methodStructure category;
+                        cr;
+                        nextPutAll: (methodStructure source withLineEndings: String lfString) ]
+
+    "Modified: / 30-08-2012 / 14:49:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 writePackageStructure
--- a/CypressStructure.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/CypressStructure.st	Thu Aug 30 12:55:16 2012 +0000
@@ -55,46 +55,51 @@
 
 fromPackage: aCypressPackageDefinition
 
-	| snapshot classMap classDefinitions classStructure |
-	snapshot := aCypressPackageDefinition snapshot.
-	name := aCypressPackageDefinition name, '.package'.
-	properties := Dictionary new.
-	classDefinitions := Set new.
-	classMap := Dictionary new.
-	snapshot definitions do: [:definition |  
-			definition 
-				classDefinition: [:classDefinition |  classDefinitions add: classDefinition ] 
-				methodDefinition: [:methodDefinition | 
-					(classMap 
-						at: methodDefinition className 
-						ifAbsent: [classMap at: methodDefinition className put: Set new]) 
-							add: methodDefinition. ]].
-	classDefinitions do: [:classDefinition | 
-		classStructure := (CypressClassStructure fromClassDefinition: classDefinition)
-			packageStructure: self.
-		(classMap removeKey: classDefinition className ifAbsent: [#()]) do: [:methodDefinition | | methodStructure |
-			methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
-				packageStructure: self;
-				classStructure: classStructure.
-			(methodDefinition
-				instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
-				classMethod: [:classMethod | classStructure classMethods ])
-					at: methodDefinition selector
-					put: methodStructure ].
-		self classes add: classStructure ].
-	classMap keysAndValuesDo: [:className :methods |
-		classStructure := (CypressClassStructure new name: className)
-			packageStructure: self.
-		methods do: [:methodDefinition | | methodStructure |
-			methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
-				packageStructure: self;
-				classStructure: classStructure.
-			(methodDefinition
-				instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
-				classMethod: [:classMethod | classStructure classMethods ])
-					at: methodDefinition selector
-					put: methodStructure ].
-		self extensions add: classStructure ].
+        | snapshot classMap classDefinitions classStructure |
+        snapshot := aCypressPackageDefinition snapshot.
+        name := ((aCypressPackageDefinition name 
+                    copyReplaceAll: $: with:$_)
+                    replaceAll: $/ with: $_)
+                    , '.package'.
+        properties := Dictionary new.
+        classDefinitions := Set new.
+        classMap := Dictionary new.
+        snapshot definitions do: [:definition |  
+                        definition 
+                                classDefinition: [:classDefinition |  classDefinitions add: classDefinition ] 
+                                methodDefinition: [:methodDefinition | 
+                                        (classMap 
+                                                at: methodDefinition className 
+                                                ifAbsent: [classMap at: methodDefinition className put: Set new]) 
+                                                        add: methodDefinition. ]].
+        classDefinitions do: [:classDefinition | 
+                classStructure := (CypressClassStructure fromClassDefinition: classDefinition)
+                        packageStructure: self.
+                (classMap removeKey: classDefinition className ifAbsent: [#()]) do: [:methodDefinition | | methodStructure |
+                        methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
+                                packageStructure: self;
+                                classStructure: classStructure.
+                        (methodDefinition
+                                instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
+                                classMethod: [:classMethod | classStructure classMethods ])
+                                        at: methodDefinition selector
+                                        put: methodStructure ].
+                self classes add: classStructure ].
+        classMap keysAndValuesDo: [:className :methods |
+                classStructure := (CypressClassStructure new name: className)
+                        packageStructure: self.
+                methods do: [:methodDefinition | | methodStructure |
+                        methodStructure := (CypressMethodStructure fromMethodDefinition: methodDefinition)
+                                packageStructure: self;
+                                classStructure: classStructure.
+                        (methodDefinition
+                                instanceMethod: [:instanceMethod | classStructure instanceMethods ] 
+                                classMethod: [:classMethod | classStructure classMethods ])
+                                        at: methodDefinition selector
+                                        put: methodStructure ].
+                self extensions add: classStructure ].
+
+    "Modified: / 30-08-2012 / 14:36:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressStructure methodsFor:'writing'!
--- a/cypress.rc	Thu Aug 30 12:26:00 2012 +0000
+++ b/cypress.rc	Thu Aug 30 12:55:16 2012 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 1998-2012\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.1\0"
-      VALUE "ProductDate", "Thu, 30 Aug 2012 12:25:51 GMT\0"
+      VALUE "ProductDate", "Thu, 30 Aug 2012 12:54:55 GMT\0"
     END
 
   END
--- a/extensions.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/extensions.st	Thu Aug 30 12:55:16 2012 +0000
@@ -11,18 +11,20 @@
 
 writeCypressJsonOn: aStream forHtml: forHtml indent: startIndent
 
-	| indent |
-	aStream 
-		nextPutAll: '[';
-		newLine.
-	indent := startIndent + 1.
-	1 to: self size do: [:index | | item | 
-		item := self at: index.
-		aStream tab: indent.
-		item writeCypressJsonOn: aStream forHtml: forHtml indent: indent.
-		index < self size ifTrue: [ aStream nextPutAll: ','; newLine ]].
-	self size = 0 ifTrue: [ aStream tab: indent ].
-	aStream nextPutAll: ' ]'
+        | indent |
+        aStream 
+                nextPutAll: '[';
+                cr.
+        indent := startIndent + 1.
+        1 to: self size do: [:index | | item | 
+                item := self at: index.
+                aStream tab: indent.
+                item writeCypressJsonOn: aStream forHtml: forHtml indent: indent.
+                index < self size ifTrue: [ aStream nextPutAll: ','; cr ]].
+        self size = 0 ifTrue: [ aStream tab: indent ].
+        aStream nextPutAll: ' ]'
+
+    "Modified: / 30-08-2012 / 14:51:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Boolean methodsFor:'*Cypress-Structure'!
@@ -97,10 +99,10 @@
     indent := startIndent.
     aStream
         nextPutAll: '{';
-        newLine.
+        cr.
     count := 0.
     indent := indent + 1.
-    (self keys sort: [ :a :b | a <= b ])
+    (self keys asSortedCollection: [ :a :b | a <= b ])
         do: [ :key | 
             | value |
             value := self at: key.
@@ -113,10 +115,12 @@
                 ifTrue: [ 
                     aStream
                         nextPutAll: ',';
-                        newLine ] ].
+                        cr ] ].
     self size = 0
         ifTrue: [ aStream tab: indent ].
     aStream nextPutAll: ' }'
+
+    "Modified: / 30-08-2012 / 14:51:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Method methodsFor:'converting'!
--- a/stx_goodies_cypress.st	Thu Aug 30 12:26:00 2012 +0000
+++ b/stx_goodies_cypress.st	Thu Aug 30 12:55:16 2012 +0000
@@ -157,7 +157,7 @@
     "Return a SVN revision number of myself.
      This number is updated after a commit"
 
-    ^ "$SVN-Revision:"'3               '"$"
+    ^ "$SVN-Revision:"'4               '"$"
 ! !
 
 !stx_goodies_cypress class methodsFor:'documentation'!