- CypressStructure
authorjv
Fri, 31 Aug 2012 18:32:17 +0000
changeset 6 65414b4bbe93
parent 5 0fd3156a3a9f
child 7 dce8e52bd7ea
- CypressStructure added: #asChangeSet #asChangeSetOn: #changesInto: #changesOn: - CypressPackageStructure added: #changesInto: #changesOn: changed: #fromPackage: - CypressClassStructure added: #changesInto: #changesOn: - CypressMethodStructure added: #changesInto: #changesOn: #fromJs: - CypressPackageReader added: #asChangeSet changed: #readClassStructureFromEntry: #readExtensionClassStructureFromEntry: #readPackageStructure - extensions ...
CypressClassStructure.st
CypressMethodStructure.st
CypressPackageReader.st
CypressPackageStructure.st
CypressStructure.st
cypress.rc
extensions.st
--- a/CypressClassStructure.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/CypressClassStructure.st	Fri Aug 31 18:32:17 2012 +0000
@@ -119,6 +119,25 @@
 		instVarNames: self instanceVariableNames
 		classInstVarNames: self classInstanceVariableNames
 		comment: self comment
+!
+
+changesOn:aStream
+    | def |
+
+    isClassExtension ifFalse:[
+        def := ClassDefinitionChange new.
+        def superClassName: (properties at: #super).
+        def className: (properties at: #name).
+        def instanceVariableNames: (String streamContents:[:s|((properties at: #instvars ifAbsent:[#()])) do:[:i|s nextPutAll:i; space]]).
+        def classInstanceVariableNames: (String streamContents:[:s|((properties at: #classinstvars ifAbsent:[#()]) ) do:[:i|s nextPutAll:i; space]]).
+        def classVariableNames: (String streamContents:[:s|((properties at: #classvars ifAbsent:[#()] ) ) do:[:i|s nextPutAll:i; space]]).
+        aStream nextPut: def.
+    ].
+
+    instanceMethods ? #() do:[:each|each changesOn: aStream].
+    classMethods ? #()  do:[:each|each changesOn: aStream].
+
+    "Modified: / 31-08-2012 / 19:23:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressClassStructure methodsFor:'initialization'!
--- a/CypressMethodStructure.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/CypressMethodStructure.st	Fri Aug 31 18:32:17 2012 +0000
@@ -118,10 +118,35 @@
 		category: self category
 		source: self source
 		timeStamp: self timeStamp
+!
+
+changesOn:aStream
+    | change parser |
+
+    change := MethodDefinitionChange new.
+    change className: (classStructure properties at:#name).
+    isMetaclass ifTrue:[
+        change className: (change className , ' class')
+    ].
+    change category: (properties at:#category).
+
+    parser := Parser parseMethodSpecification: source. 
+    change selector: parser selector.
+    change source: source.
+
+    aStream nextPut: change
+
+    "Modified: / 31-08-2012 / 19:25:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressMethodStructure methodsFor:'initialization'!
 
+fromJs:jsObject
+    "superclass CypressStructure says that I am responsible to implement this method"
+
+    ^ self shouldImplement
+!
+
 fromJs: jsObject  named: methodNameParts
 
 	| ext |
--- a/CypressPackageReader.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/CypressPackageReader.st	Fri Aug 31 18:32:17 2012 +0000
@@ -62,6 +62,14 @@
 	packageStructure := aPackageStructure
 ! !
 
+!CypressPackageReader methodsFor:'converting'!
+
+asChangeSet
+    ^packageStructure asChangeSet
+
+    "Created: / 31-08-2012 / 20:05:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !CypressPackageReader methodsFor:'private'!
 
 classStructureFrom: classPropertiesDict 
@@ -90,24 +98,18 @@
 !
 
 readClassStructureFromEntry: classEntry
-        | classDirectory methodPropertiesDict classPropertiesDict classComment entries classStructure |
+        | classDirectory methodPropertiesDict classPropertiesDict classComment entries classStructure propertyEntry |
         classDirectory := classEntry asFilename.
         entries := classDirectory directoryContentsAsFilenames.
-        (entries
-                detect: [ :entry | entry baseName = 'methodProperties.json' ]
-                ifNone: [ ]) ifNotNil: [ :propertyEntry |
-                propertyEntry readStreamDo: [ :fileStream |
-                        methodPropertiesDict := CypressJsonParser parseStream: fileStream ]].
-        (entries
-                detect: [ :entry | entry baseName = 'properties.json' ]
-                ifNone: [ ]) ifNotNil: [ :propertyEntry |
-                propertyEntry readStreamDo: [ :fileStream |
-                        classPropertiesDict := CypressJsonParser parseStream: fileStream ]].
-        (entries
-                detect: [ :entry | entry baseName = 'README.md' ]
-                ifNone: [ ]) ifNotNil: [ :commentEntry |
-                commentEntry readStreamDo: [ :fileStream |
-                        classComment := fileStream contents ]].
+        propertyEntry := entries detect: [ :entry | entry baseName = 'properties.json' ] ifNone: [ nil ] .
+        propertyEntry notNil ifTrue:[
+            propertyEntry readingFileDo: [ :fileStream | classPropertiesDict := CypressJsonParser parseStream: fileStream ].
+        ].
+        propertyEntry := entries detect: [ :entry | entry baseName = 'README.md' ] ifNone: [ nil ] .
+        propertyEntry notNil ifTrue:[
+            propertyEntry readingFileDo: [ :fileStream | classComment := fileStream contents ].
+        ].
+
         classStructure := self
                 classStructureFrom: classPropertiesDict
                 comment: classComment.
@@ -117,24 +119,21 @@
                 methodProperties: methodPropertiesDict.
         ^ classStructure.
 
-    "Modified: / 31-08-2012 / 09:21:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-08-2012 / 19:54:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 readExtensionClassStructureFromEntry: classEntry
-        | classDirectory methodPropertiesDict classPropertiesDict entries classStructure |
+        | classDirectory methodPropertiesDict classPropertiesDict entries classStructure propertyEntry |
 
         classDirectory := classEntry asFilename.
         entries := classDirectory directoryContentsAsFilenames.
-        (entries
-                detect: [ :entry | entry baseName = 'methodProperties.json' ]
-                ifNone: [ ]) ifNotNil: [ :propertyEntry |
-                propertyEntry readStreamDo: [ :fileStream |
-                        methodPropertiesDict := CypressJsonParser parseStream: fileStream ]].
-        (entries
-                detect: [ :entry | entry baseName = 'properties.json' ]
-                ifNone: [ ]) ifNotNil: [ :propertyEntry |
-                propertyEntry readStreamDo: [ :fileStream |
-                        classPropertiesDict := CypressJsonParser parseStream: fileStream ]].
+
+        propertyEntry := entries detect: [ :entry | entry baseName = 'properties.json' ] ifNone: [ nil ] .
+        propertyEntry notNil ifTrue:[
+            propertyEntry readingFileDo: [ :fileStream | classPropertiesDict := CypressJsonParser parseStream: fileStream ].
+        ].
+
+
         classStructure := self classStructureFrom: classPropertiesDict.
         self
                 readMethodStructureFor: classStructure
@@ -142,7 +141,7 @@
                 methodProperties: methodPropertiesDict.
         ^ classStructure
 
-    "Modified: / 31-08-2012 / 09:21:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-08-2012 / 19:55:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 readMethodStructureFor: classStructure in: entries methodProperties: methodPropertiesDict
@@ -183,7 +182,7 @@
 
 readPackageStructure
     packageStructure := CypressPackageStructure new.
-    packageStructure name: (properties at: #name) .
+    packageStructure name: (properties at: #'_stx_name') .
 
     self packageDirectory directoryContentsAsFilenamesDo: [ :entry |
             entry name first ~= $. ifTrue: [
@@ -192,7 +191,7 @@
                     (entry name endsWith: '.extension') ifTrue: [
                             self packageStructure extensions add: (self readExtensionClassStructureFromEntry: entry) ]]]
 
-    "Modified: / 30-08-2012 / 15:18:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 31-08-2012 / 19:56:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 readPropertiesFile      
--- a/CypressPackageStructure.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/CypressPackageStructure.st	Fri Aug 31 18:32:17 2012 +0000
@@ -53,6 +53,17 @@
 	^self
 ! !
 
+!CypressPackageStructure methodsFor:'converting'!
+
+changesOn:aStream
+    "superclass CypressStructure says that I am responsible to implement this method"
+
+    classes do:[:cls | cls changesOn: aStream ].
+    extensions do:[:ext | ext changesOn: aStream ].
+
+    "Modified: / 31-08-2012 / 20:03:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !CypressPackageStructure methodsFor:'initialization'!
 
 fromJs: jsObject
@@ -85,7 +96,7 @@
                     yourself)
                     , '.package'.
         properties := Dictionary new.
-        properties at: 'name' put: aCypressPackageDefinition name.
+        properties at: '_stx_name' put: aCypressPackageDefinition name.
         classDefinitions := Set new.
         classMap := Dictionary new.
         snapshot definitions do: [:definition |  
@@ -123,7 +134,7 @@
                                         put: methodStructure ].
                 self extensions add: classStructure ].
 
-    "Modified: / 30-08-2012 / 15:10:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-08-2012 / 19:56:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CypressPackageStructure methodsFor:'snapshotting'!
--- a/CypressStructure.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/CypressStructure.st	Fri Aug 31 18:32:17 2012 +0000
@@ -46,6 +46,22 @@
 	^properties
 ! !
 
+!CypressStructure methodsFor:'converting'!
+
+asChangeSet
+
+    ^ChangeSet streamContents:[:changeStream | self changesOn: changeStream ]
+
+    "Created: / 31-08-2012 / 20:01:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changesOn: aStream
+
+    self subclassResponsibility
+
+    "Created: / 31-08-2012 / 20:02:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !CypressStructure methodsFor:'initialization'!
 
 fromJs: jsObject
--- a/cypress.rc	Fri Aug 31 07:27:24 2012 +0000
+++ b/cypress.rc	Fri Aug 31 18:32:17 2012 +0000
@@ -3,7 +3,7 @@
 // automagically generated from the projectDefinition: stx_goodies_cypress.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     6,2,2,2
+  FILEVERSION     6,2,6,6
   PRODUCTVERSION  6,2,3,1
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
@@ -20,12 +20,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Class library (LIB)\0"
-      VALUE "FileVersion", "6.2.2.2\0"
+      VALUE "FileVersion", "6.2.6.6\0"
       VALUE "InternalName", "stx:goodies/cypress\0"
       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", "Fri, 31 Aug 2012 07:26:55 GMT\0"
+      VALUE "ProductDate", "Fri, 31 Aug 2012 18:32:14 GMT\0"
     END
 
   END
--- a/extensions.st	Fri Aug 31 07:27:24 2012 +0000
+++ b/extensions.st	Fri Aug 31 18:32:17 2012 +0000
@@ -132,7 +132,7 @@
                 classIsMeta: self methodClass isMeta
                 selector: self selector
                 category: self category
-                source: self getSource
+                source: self source
                 timeStamp: self timeStamp
 
     "Created: / 30-08-2012 / 14:05:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"