- First shot
authorjv
Thu, 30 Aug 2012 11:46:39 +0000
changeset 1 8a5b7afa28ff
parent 0 c81148cde6d9
child 2 a26b35650f67
- First shot
CypressAbstractTest.st
CypressAddition.st
CypressClassDefinition.st
CypressClassStructure.st
CypressDefinition.st
CypressDefinitionIndex.st
CypressDefinitionTest.st
CypressDependencySorter.st
CypressJsonParser.st
CypressLoader.st
CypressLoaderTest.st
CypressMethodDefinition.st
CypressMethodStructure.st
CypressMockBasic.st
CypressModification.st
CypressPackageDefinition.st
CypressPackageReader.st
CypressPackageStructure.st
CypressPackageWriter.st
CypressPatch.st
CypressPatchOperation.st
CypressPatchTest.st
CypressRemoval.st
CypressSnapshot.st
CypressSnapshotTest.st
CypressStructure.st
CypressStructureTest.st
Make.proto
Make.spec
Makefile
abbrev.stc
bc.mak
bmake.bat
cypress.rc
extensions.st
lcmake.bat
libInit.cc
stx_goodies_cypress.st
vcmake.bat
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressAbstractTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,308 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+TestCase subclass:#CypressAbstractTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressAbstractTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressAbstractTest methodsFor:'private'!
+
+baseDefinitions
+	| className |
+	className := 'CypressMockBasic'.
+	^{
+		(CypressClassDefinition
+        		name: className
+       		 	superclassName: 'Object'
+       			category: 'Cypress-Mocks'
+                       	instVarNames: #('name')
+			classInstVarNames: #('current')
+        		comment:  'This mock contains basic class and instance method selectors').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'extra'
+        		category: 'accessing'
+        		source:'extra
+	"extra method"').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'initialize'
+        		category: 'initialization'
+        		source:'initialize
+	super initialize.
+	self name: ''Unknown''').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'name'
+        		category: 'accessing'
+        		source:'name
+	^name').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'name:'
+        		category: 'accessing'
+        		source:'name: aString
+	name := aString').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'current'
+        		category: 'accessing'
+        		source:'current
+	^current').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'current:'
+        		category: 'accessing'
+        		source:'current: anObject
+	current := anObject').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'initialize'
+        		category: 'initialization'
+        		source:'initialize
+	self current: self new').
+   	 	(CypressMethodDefinition
+          		className: 'Object'
+        		classIsMeta: false
+        		selector: 'isCypressMockBasic'
+        		category: '*Cypress-Mocks'
+        		source:'isCypressMockBasic
+	^false')
+	}
+!
+
+basePackageStructureJson
+    ^ '{
+	"name" : "Cypress-Mocks.package",
+	"contents" : [
+		{
+			"name" : "CypressMockBasic.class",
+			"instance" : [
+				{
+					"name" : "extra.st",
+					"contents" : "accessing%0Aextra%0A%09%22extra%20method%22"
+				 },
+				{
+					"name" : "initialize.st",
+					"contents" : "initialization%0Ainitialize%0A%09super%20initialize.%0A%09self%20name%3A%20%27Unknown%27"
+				 },
+				{
+					"name" : "name.st",
+					"contents" : "accessing%0Aname%0A%09%5Ename"
+				 },
+				{
+					"name" : "name..st",
+					"contents" : "accessing%0Aname%3A%20aString%0A%09name%20%3A%3D%20aString"
+				 }			],
+			"class" : [
+				{
+					"name" : "current.st",
+					"contents" : "accessing%0Acurrent%0A%09%5Ecurrent"
+				 },
+				{
+					"name" : "current..st",
+					"contents" : "accessing%0Acurrent%3A%20anObject%0A%09current%20%3A%3D%20anObject"
+				 },
+				{
+					"name" : "initialize.st",
+					"contents" : "initialization%0Ainitialize%0A%09self%20current%3A%20self%20new"
+				 }			],
+			"README.md" : "This%20mock%20contains%20basic%20class%20and%20instance%20method%20selectors",
+			"properties.json" : {
+				"classinstvars" : [
+					"current" ],
+				"instvars" : [
+					"name" ],
+				"name" : "CypressMockBasic",
+				"super" : "Object" }
+		 },
+		{
+			"name" : "Object.extension",
+			"instance" : [
+				{
+					"name" : "isCypressMockBasic.st",
+					"contents" : "%2ACypress-Mocks%0AisCypressMockBasic%0A%09%5Efalse"
+				 }			],
+			"class" : [
+			],
+			"properties.json" : {
+				"name" : "Object" }
+		 }
+	],
+	"properties.json" : {
+		 }
+}'
+!
+
+baseTargetPatch
+	| className |
+	className := 'CypressMockBasic'.
+	^{
+		(CypressAddition 
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'added'
+        			category: 'accessing'
+        			source:'added
+	"added method"')).
+		(CypressModification 
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'name:'
+        			category: 'accessing'
+        			source:'name: aString
+	name := aString') 
+			to: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'name:'
+        			category: 'accessing'
+        			source:'name: aString
+	"changed method"
+	name := aString')).
+		(CypressRemoval 
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'extra'
+        			category: 'accessing'
+        			source:'extra
+	"extra method"')).
+		(CypressRemoval 
+			of: (CypressMethodDefinition
+          			className: 'Object'
+        			classIsMeta: false
+        			selector: 'isCypressMockBasic'
+        			category: '*Cypress-Mocks'
+        			source:'isCypressMockBasic
+	^false'))
+	}
+!
+
+classComment
+
+	^'This mock contains basic class and instance method selectors'
+!
+
+compileJSON: aJsonString
+
+	^CypressJsonParser parse: aJsonString
+!
+
+sampleJson
+
+	^'{
+	"age" : 25,
+	"name" : "John%20Smith",
+	"phoneNumber" : [
+		{
+			"number" : "212%20555-1234",
+			"type" : "home" },
+		{
+			"number" : "646%20555-4567",
+			"type" : "fax" } ],
+	"registered" : true }'
+!
+
+targetDefinitions
+	"remove #extra method and modify #name: method"
+
+	| className |
+	className := 'CypressMockBasic'.
+	^{
+		(CypressClassDefinition
+        		name: className
+       		 	superclassName: 'Object'
+       			category: 'Cypress-Mocks'
+                       	instVarNames: #('name')
+			classInstVarNames: #('current')
+        		comment: self classComment).
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'added'
+        		category: 'accessing'
+        		source:'added
+	"added method"').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'initialize'
+        		category: 'initialization'
+        		source:'initialize
+	super initialize.
+	self name: ''Unknown''').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'name'
+        		category: 'accessing'
+        		source:'name
+	^name').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: false
+        		selector: 'name:'
+        		category: 'accessing'
+        		source:'name: aString
+	"changed method"
+	name := aString').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'current'
+        		category: 'accessing'
+        		source:'current
+	^current').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'current:'
+        		category: 'accessing'
+        		source:'current: anObject
+	current := anObject').
+   	 	(CypressMethodDefinition
+          		className: className
+        		classIsMeta: true
+        		selector: 'initialize'
+        		category: 'initialization'
+        		source:'initialize
+	self current: self new')
+	}
+!
+
+validatePackage: package against: expectedDefinitions
+
+	| packageDefinitions cd1 cd2 |
+	packageDefinitions := package snapshot definitions.
+	self assert: (expectedDefinitions size = packageDefinitions size).
+	cd1 := packageDefinitions detect: [:each | each isKindOf: CypressClassDefinition].
+	cd2 :=  expectedDefinitions detect: [:each | each isKindOf: CypressClassDefinition].
+	self assert: cd1 = cd2.
+	packageDefinitions do: [:def |
+		(expectedDefinitions includes: def)
+			ifFalse: [ 
+				def inspect.
+				self assert: false ]].
+! !
+
+!CypressAbstractTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressAddition.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,98 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressPatchOperation subclass:#CypressAddition
+	instanceVariableNames:'definition'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressAddition comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressAddition class methodsFor:'instance creation'!
+
+of: aDefinition
+	^ self new definition: aDefinition
+! !
+
+!CypressAddition methodsFor:'accessing'!
+
+definition
+
+	^definition
+!
+
+description
+    ^ 'add: ' , self definition printString
+! !
+
+!CypressAddition methodsFor:'applying'!
+
+applyTo: aCypressLoader
+
+	aCypressLoader applyAddition: self
+! !
+
+!CypressAddition methodsFor:'comparing'!
+
+= aPatchOperation
+	^(super = aPatchOperation) and: [self definition = aPatchOperation definition]
+! !
+
+!CypressAddition methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	^self definition provisions
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^self definition requirements
+! !
+
+!CypressAddition methodsFor:'initialization'!
+
+definition: aDefinition
+
+	definition := aDefinition
+! !
+
+!CypressAddition methodsFor:'loading'!
+
+loadClassDefinition
+
+	self definition loadClassDefinition
+!
+
+loadMethodDefinition
+	self definition loadMethodDefinition
+!
+
+postLoadDefinition
+	self definition postLoadOver: nil
+! !
+
+!CypressAddition methodsFor:'printing'!
+
+printString
+
+	| str |
+	str := WriteStream on: String new.
+	str 
+		nextPutAll: super printString;
+		nextPutAll: ' (';
+		nextPutAll: self description;
+		nextPutAll: ')'.
+	^str contents
+! !
+
+!CypressAddition class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressClassDefinition.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,192 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressDefinition subclass:#CypressClassDefinition
+	instanceVariableNames:'name superclassName category comment instVarNames
+		classInstVarNames'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressClassDefinition comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressClassDefinition class methodsFor:'instance creation'!
+
+name: aClassName 
+superclassName: aSuperclassName
+category: aCategory
+instVarNames: anInstanceVariableNames
+classInstVarNames: aClassInstanceVariableNames
+comment: aComment
+
+	^(self new) 
+		name: aClassName 
+		superclassName: aSuperclassName
+		category: aCategory
+		instVarNames: anInstanceVariableNames
+		classInstVarNames: aClassInstanceVariableNames
+		comment: aComment
+! !
+
+!CypressClassDefinition methodsFor:'accessing'!
+
+category
+
+	^category
+!
+
+classInstVarNames
+
+	^classInstVarNames
+!
+
+className
+
+	^self name
+!
+
+comment
+
+	^comment
+!
+
+description
+
+	^ Array with: name
+!
+
+instVarNames
+
+	^instVarNames
+!
+
+name
+
+	^name
+!
+
+superclassName
+
+	^superclassName
+! !
+
+!CypressClassDefinition methodsFor:'comparing'!
+
+= aDefinition
+	^(super = aDefinition)
+		and: [superclassName = aDefinition superclassName
+		and: [category = aDefinition category
+		and: [instVarNames = aDefinition instVarNames
+		and: [classInstVarNames = aDefinition classInstVarNames
+		and: [comment = aDefinition comment]]]]]
+!
+
+hash
+    | hash |
+    hash := String stringHash: name initialHash: 0.
+    hash := String stringHash: superclassName initialHash: hash.
+    hash := String stringHash: (category ifNil: [ '' ]) initialHash: hash.
+    instVarNames , classInstVarNames do: [ :vName | hash := String stringHash: vName initialHash: hash ].
+    ^ hash
+! !
+
+!CypressClassDefinition methodsFor:'converting'!
+
+asCypressClassDefinition
+
+	^self
+! !
+
+!CypressClassDefinition methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	^{ self name }
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^{self superclassName}
+! !
+
+!CypressClassDefinition methodsFor:'initialization'!
+
+name: aClassName superclassName: aSuperclassName category: aCategory instVarNames: anInstanceVariableNames classInstVarNames: aClassInstanceVariableNames comment: aComment
+
+	name := aClassName asSymbol.
+	superclassName := aSuperclassName asSymbol.
+	category := aCategory asSymbol.
+	instVarNames := anInstanceVariableNames.
+	classInstVarNames := aClassInstanceVariableNames.
+	comment := aComment
+! !
+
+!CypressClassDefinition methodsFor:'loading'!
+
+actualClass
+
+	^Smalltalk at: self name
+!
+
+createClass
+
+	| superClass |
+	superClass := Smalltalk at: self superclassName.
+	^ClassBuilder new
+		superclass: superClass 
+		subclass: self name
+		instanceVariableNames: (self stringForVariables: self instVarNames)
+		classVariableNames: '' poolDictionaries: '' category: self category
+!
+
+loadClassDefinition
+
+	 | cls |
+	cls := self createClass.
+	cls class instanceVariableNames: (self stringForVariables: self classInstVarNames).
+	self comment notEmpty ifTrue: [ cls comment: self comment ]
+!
+
+unloadDefinition
+
+	Smalltalk removeClass: self actualClass.
+! !
+
+!CypressClassDefinition methodsFor:'printString'!
+
+printString
+
+	| str |
+	str := WriteStream on: String new.
+	str 
+		nextPutAll: super printString;
+		nextPutAll: ' (';
+		nextPutAll: self name;
+		nextPutAll: ')'.
+	^str contents
+!
+
+stringForVariables: aCollectionOfVariableNames
+	^ String streamContents:
+		[:stream |
+		aCollectionOfVariableNames
+			do: [:ea | stream nextPutAll: ea]
+			separatedBy: [stream space]]
+! !
+
+!CypressClassDefinition methodsFor:'visiting'!
+
+classDefinition: classBlock methodDefinition: methodBlock
+
+	classBlock value: self
+! !
+
+!CypressClassDefinition class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressClassStructure.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,264 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressStructure subclass:#CypressClassStructure
+	instanceVariableNames:'instanceMethods classMethods comment isClassExtension'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressClassStructure comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressClassStructure class methodsFor:'instance creation'!
+
+fromClassDefinition: classDefinition
+
+	^self new
+		fromClassDefinition: classDefinition;
+		yourself
+! !
+
+!CypressClassStructure methodsFor:'accessing'!
+
+category
+
+	^self packageStructure packageName
+!
+
+classInstanceVariableNames
+	^self properties at: 'classinstvars' ifAbsent: ['']
+!
+
+classInstanceVariableNames: aString
+	^self properties at: 'classinstvars' put: aString
+!
+
+classMethods
+
+	classMethods ifNil: [ classMethods := Dictionary new ].
+	^classMethods
+!
+
+className
+
+	^self name
+!
+
+comment
+
+	comment ifNil: [ comment := '' ].
+	^comment
+!
+
+comment: aString
+
+	comment := aString
+!
+
+instanceMethods
+
+	instanceMethods ifNil: [ instanceMethods := Dictionary new ].
+	^instanceMethods
+!
+
+instanceVariableNames
+
+	^self properties at: 'instvars' ifAbsent: ['']
+!
+
+instanceVariableNames: aString
+
+	^self properties at: 'instvars' put: aString
+!
+
+isClassExtension
+
+        isClassExtension ifNil: [ isClassExtension := true ].
+        ^isClassExtension
+!
+
+isClassExtension: aBoolean
+
+	isClassExtension := aBoolean
+!
+
+name
+
+	^self properties at: 'name'
+!
+
+name: aString
+
+	self properties at: 'name' put: aString
+!
+
+properties: classPropertiesDict
+	properties _ classPropertiesDict
+!
+
+superclassName
+
+	^self properties at: 'super'
+!
+
+superclassName: aString
+
+	^self properties at: 'super' put: aString
+! !
+
+!CypressClassStructure methodsFor:'converting'!
+
+asCypressClassDefinition
+	self isClassExtension ifTrue: [ ^nil ].
+	^CypressClassDefinition
+		name: self className
+		superclassName: self superclassName
+		category: self category 
+		instVarNames: self instanceVariableNames
+		classInstVarNames: self classInstanceVariableNames
+		comment: self comment
+! !
+
+!CypressClassStructure methodsFor:'initialization'!
+
+fromClassDefinition: classDefinition
+
+	self isClassExtension: false.
+	self name: classDefinition name.
+	self comment: classDefinition comment.
+  	self superclassName: classDefinition superclassName.
+	self instanceVariableNames: classDefinition instVarNames.
+	self classInstanceVariableNames: classDefinition classInstVarNames.
+!
+
+fromJs: jsObject
+
+	properties := jsObject at: 'properties.json'.
+	(jsObject at: 'class' ifAbsent: [#()]) do: [:jsMethodObject |  | methodNameParts |
+		methodNameParts := self splitMethodNameFor: jsMethodObject.
+		(self classMethodNamed: (methodNameParts at: 1)) 
+			packageStructure: self packageStructure;
+			classStructure: self;
+			isMetaclass: true;
+			fromJs: jsMethodObject named: methodNameParts ].
+	(jsObject at: 'instance' ifAbsent: [#()]) do: [:jsMethodObject |  | methodNameParts |
+		methodNameParts := self splitMethodNameFor: jsMethodObject.
+		(self instanceMethodNamed: (methodNameParts at: 1)) 
+			packageStructure: self packageStructure;
+			classStructure: self;
+			fromJs: jsMethodObject named: methodNameParts ].	
+	comment := jsObject at: 'README.md' ifAbsent: ['']
+! !
+
+!CypressClassStructure methodsFor:'private'!
+
+splitMethodName: methodName
+
+	| ext  |
+	ext := '.json'.
+	(   '*' , ext match: methodName)
+		ifFalse: [
+			ext := '.st'.
+			('*' , ext match: methodName)
+				ifFalse: [ self error: 'invalid structure element: ', methodName ] ].
+	^{methodName copyFrom: 1 to: (methodName size - ext size). ext}
+!
+
+splitMethodNameFor: jsMethodObject
+
+	^self splitMethodName: (jsMethodObject at: 'name')
+! !
+
+!CypressClassStructure methodsFor:'querying'!
+
+classMethodNamed: methodName
+
+	^self classMethods 
+		at: methodName 
+		ifAbsent: [ self classMethods at: methodName put: (CypressMethodStructure new name: methodName) ]
+!
+
+instanceMethodNamed: methodName
+
+	^self instanceMethods 
+		at: methodName 
+		ifAbsent: [ self instanceMethods at: methodName put: (CypressMethodStructure new name: methodName) ]
+! !
+
+!CypressClassStructure methodsFor:'writing'!
+
+writeJsonOn: aStream  indent: startIndent
+
+        | indent methods |
+        indent := startIndent.
+        aStream 
+                tab: indent;
+                nextPutAll: '{';
+                newLine.
+        indent := indent + 1.
+        aStream
+                tab: indent;
+                nextPutAll: '"name"';
+                nextPutAll: ' : ';
+                nextPutAll: '"', self name, (self isClassExtension ifTrue: [ '.extension' ] ifFalse: [ '.class' ]), '",';
+                newLine.
+        aStream
+                tab: indent;
+                nextPutAll: '"instance" : [';
+                newLine;
+                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 ]].
+        aStream
+                tab: indent;
+                nextPutAll: '],';
+                newLine;
+                yourself.
+        aStream
+                tab: indent;
+                nextPutAll: '"class" : [';
+                newLine;
+                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 ]].
+        aStream
+                tab: indent;
+                nextPutAll: ']'.
+        self isClassExtension
+                ifFalse: [ 
+                        aStream
+                                nextPutAll: ',';
+                                newLine;
+                                tab: indent;
+                                nextPutAll: '"README.md" : ';
+                                yourself.
+                        self comment writeCypressJsonOn: aStream forHtml: true indent: indent ].
+        aStream
+                nextPutAll: ',';
+                newLine;
+                tab: indent;
+                nextPutAll: '"properties.json" : ';
+                yourself.
+        self properties writeCypressJsonOn: aStream forHtml: true indent: indent.
+        indent := indent - 1.
+        aStream
+                newLine;
+                tab: indent;
+                nextPutAll: ' }'
+
+    "Modified: / 30-08-2012 / 13:31:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CypressClassStructure class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressDefinition.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,89 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressDefinition
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressDefinition comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressDefinition methodsFor:'accessing'!
+
+description
+	self subclassResponsibility
+! !
+
+!CypressDefinition methodsFor:'comparing'!
+
+= aDefinition
+	^(aDefinition isKindOf: CypressDefinition) and: [self isRevisionOf: aDefinition]
+! !
+
+!CypressDefinition methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	^#()
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^#()
+! !
+
+!CypressDefinition methodsFor:'loading'!
+
+actualClass
+
+	self subclassResponsibility
+!
+
+loadClassDefinition
+	"default is to do nothing"
+!
+
+loadMethodDefinition
+	"default is to do nothing"
+!
+
+postLoad
+	"noop"
+!
+
+postLoadOver: aDefinition
+
+	self postLoad
+!
+
+unloadDefinition
+
+	self subclassResponsibility
+! !
+
+!CypressDefinition methodsFor:'testing'!
+
+isRevisionOf: aDefinition
+	^ (aDefinition isKindOf: CypressDefinition) and: [aDefinition description = self description]
+!
+
+isSameRevisionAs: aDefinition
+	^ self = aDefinition
+! !
+
+!CypressDefinition methodsFor:'visiting'!
+
+classDefinition: classBlock methodDefinition: methodBlock
+	"default is noop"
+! !
+
+!CypressDefinition class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressDefinitionIndex.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,61 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressDefinitionIndex
+	instanceVariableNames:'definitionMap'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressDefinitionIndex comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressDefinitionIndex class methodsFor:'instance creation'!
+
+definitions: aCollection
+	^ self new addAll: aCollection
+! !
+
+!CypressDefinitionIndex methodsFor:'accessing'!
+
+definitionMap
+	definitionMap ifNil: [ definitionMap := Dictionary new ].
+	^ definitionMap
+!
+
+definitions
+	^self definitionMap values
+! !
+
+!CypressDefinitionIndex methodsFor:'adding'!
+
+add: aDefinition
+	^ self definitionMap at: aDefinition description put: aDefinition
+!
+
+addAll: aCollection
+	aCollection do: [:ea | self add: ea]
+! !
+
+!CypressDefinitionIndex methodsFor:'querying'!
+
+definitionLike: aDefinition ifPresent: foundBlock ifAbsent: errorBlock
+	| definition |
+	definition := self definitionMap at: aDefinition description ifAbsent: [].
+	^ definition
+		ifNil: errorBlock
+		ifNotNil: [foundBlock value: definition]
+! !
+
+!CypressDefinitionIndex methodsFor:'removing'!
+
+remove: aDefinition
+	self definitionMap removeKey: aDefinition description ifAbsent: []
+! !
+
+!CypressDefinitionIndex class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressDefinitionTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,83 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressAbstractTest subclass:#CypressDefinitionTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressDefinitionTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressDefinitionTest methodsFor:'testing'!
+
+testClassDefinition
+	self assert: (CypressClassDefinition
+		name: 'Foo'
+       		 superclassName: 'Object'
+       		category: 'Foo'
+                instVarNames: #()
+		classInstVarNames: #()
+        	comment: '') printString =  'a CypressClassDefinition (Foo)'
+!
+
+testDictionaryOfDefinitions
+
+	| dict |
+	"baseDefinitions"
+	dict := Dictionary new.
+	self baseDefinitions do: [:each | 
+		dict at: each put: each ].
+	self baseDefinitions do: [:each | 
+		self assert: (dict at: each) = each ].
+
+	"targetDefinitions"
+	dict := Dictionary new.
+	self targetDefinitions do: [:each | 
+		dict at: each put: each ].
+	self targetDefinitions do: [:each | 
+		self assert: (dict at: each) = each ].
+!
+
+testEquality
+	| pkg1 pkg2 pkg3 name |
+	name := 'Cypress-Mocks'.
+	pkg1 := CypressPackageDefinition new name: name.
+	pkg2 := CypressPackageDefinition new name: name.
+	pkg3 := CypressPackageDefinition new name: 'Nope!!'.
+
+	self assert: pkg1 equals: pkg2.
+	self deny: pkg1 = pkg3
+!
+
+testMethodDefinition
+	self assert: (CypressMethodDefinition
+		className: 'Foo'
+		classIsMeta: false
+		selector: 'isFoo'
+		category: 'testing'
+		source: 'isFoo ^true') printString = 'a CypressMethodDefinition (Foo>>isFoo)'
+!
+
+testNameEquality
+	| pkg name |
+	name := 'Cypress-Mocks'.
+	pkg := CypressPackageDefinition new name: name.
+	self assert: pkg name equals: name.
+	self deny: (pkg name = 'Nope.').
+!
+
+testPrintString
+	| name pkg |
+	name := 'Cypress-Mocks'.
+	pkg := CypressPackageDefinition new name: name.
+	self assert: 'a CypressPackageDefinition(', name, ')' equals: pkg printString.
+! !
+
+!CypressDefinitionTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressDependencySorter.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,108 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressDependencySorter
+	instanceVariableNames:'required provided orderedItems'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressDependencySorter comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressDependencySorter methodsFor:'accessing'!
+
+externalRequirements
+	| unloaded providedByUnloaded |
+	unloaded := self itemsWithMissingRequirements.
+	providedByUnloaded := (unloaded gather: [:e | e provisions]) asSet.
+	^ self required keys reject: [:globalName | providedByUnloaded includes: globalName ]
+!
+
+itemsWithMissingRequirements
+	| patchOperations |
+	patchOperations := Set new.
+	self required values do: [:aSetOfPatchOperations | patchOperations addAll: aSetOfPatchOperations ].
+	^ patchOperations
+!
+
+orderedItems
+	"ordered list of patch operations"
+
+	orderedItems ifNil: [ orderedItems := OrderedCollection new ].
+	^orderedItems
+!
+
+provided
+	"set of global names provided by definitions already loaded"
+
+	provided ifNil: [ provided := Set new ].
+	^provided
+!
+
+required
+	"dictionary of required global name mapped to list of definitions that require the global"
+
+	required ifNil: [ required := Dictionary new ].
+	^required
+! !
+
+!CypressDependencySorter methodsFor:'building'!
+
+add: aPatchOperation
+	| requirements |
+	requirements := self unresolvedRequirementsFor: aPatchOperation.
+	requirements isEmpty
+		ifTrue: [self addToOrder: aPatchOperation]
+		ifFalse: [self addRequirements: requirements for: aPatchOperation].
+	^ aPatchOperation
+!
+
+addAll: aCollection
+	aCollection do: [:aPatchOperation | self add: aPatchOperation ]
+! !
+
+!CypressDependencySorter methodsFor:'private'!
+
+addExternalProvisions: aCollection
+	(aCollection intersection: self externalRequirements)
+		do: [:globalName | self addProvision: globalName]
+!
+
+addProvision: aGlobalName
+	| newlySatisfied |
+	self provided add: aGlobalName.
+	newlySatisfied := self required removeKey: aGlobalName ifAbsent: [#()].
+	self addAll: newlySatisfied.
+!
+
+addRequirement: globalName for: aPatchOperation
+	(self itemsRequiring: globalName) add: aPatchOperation
+!
+
+addRequirements: aCollection for: aPatchOperation
+	aCollection do: [:globalName | self addRequirement: globalName for: aPatchOperation]
+!
+
+addToOrder: aPatchOperation
+	self orderedItems add: aPatchOperation.
+	aPatchOperation provisions do: [:globalName | self addProvision: globalName ].
+!
+
+itemsRequiring: globalName
+	^ self required at: globalName ifAbsentPut: [Set new]
+!
+
+unresolvedRequirementsFor: aPatchOperation
+	"Answer a list of global names that are required by <aPatchOperation>, but not 
+	 provided by patchOperations that have already been processed"
+
+	^ aPatchOperation requirements difference: self provided
+! !
+
+!CypressDependencySorter class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressJsonParser.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,307 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressJsonParser
+	instanceVariableNames:'stream'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressJsonParser comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressJsonParser class methodsFor:'instance creation'!
+
+new
+	self error: 'Instantiate the parser with a stream.'
+!
+
+on: aStream
+	^ self basicNew initializeOn: aStream
+! !
+
+!CypressJsonParser class methodsFor:'accessing'!
+
+parse: aString
+	^ self parseStream: aString readStream
+!
+
+parseStream: aStream
+	^ (self on: aStream) parse
+! !
+
+!CypressJsonParser methodsFor:'adding'!
+
+addProperty: anAssociation to: anObject
+	"Add the property anAssociation described with key and value to anObject. Subclasses might want to refine this implementation."
+	
+	^ anObject 
+		add: anAssociation;
+		yourself
+!
+
+addValue: anObject to: aCollection
+	"Add anObject to aCollection. Subclasses might want to refine this implementation."
+
+	^ aCollection copyWith: anObject
+! !
+
+!CypressJsonParser methodsFor:'creating'!
+
+createArray
+	"Create an empty collection. Subclasses might want to refine this implementation."
+
+	^ Array new
+!
+
+createFalse
+	"Create the false literal. Subclasses might want to refine this implementation."
+	
+	^ false
+!
+
+createNull
+	"Create the null literal. Subclasses might want to refine this implementation."
+
+	^ nil
+!
+
+createNumber: aString
+	"Create a number literal. Subclasses might want to refine this implementation."
+
+	^ aString asNumber
+!
+
+createObject
+	"Create an empty object. Subclasses might want to refine this implementation."
+	
+	^ Dictionary new
+!
+
+createProperty: aKey with: aValue
+	"Create an empty attribute value pair. Subclasses might want to refine this implementation."
+	
+	^ aKey -> aValue
+!
+
+createString: aString
+	"Create a string literal. Subclasses might want to refine this implementation."
+
+	^ aString
+!
+
+createTrue
+	"Create the true literal. Subclasses might want to refine this implementation."
+
+	^ true
+! !
+
+!CypressJsonParser methodsFor:'initialization'!
+
+initializeOn: aStream
+	self initialize.
+	stream := aStream
+! !
+
+!CypressJsonParser methodsFor:'parsing'!
+
+parse
+	| result |
+	result := self whitespace; parseValue.
+	stream atEnd
+		ifFalse: [ self error: 'end of input expected' ].
+	^ result
+!
+
+parseArray
+	| result |
+	self expect: '['.
+	result := self createArray.
+	(self match: ']')
+		ifTrue: [ ^ result ].
+	[ stream atEnd ] whileFalse: [
+		result := self
+			addValue: self parseValue
+			to: result.
+		(self match: ']') 
+			ifTrue: [ ^ result ].
+		self expect: ',' ].
+	self error: 'end of array expected'
+!
+
+parseObject
+	| result |
+	self expect: '{'.
+	result := self createObject.
+	(self match: '}')
+		ifTrue: [ ^ result ].
+	[ stream atEnd ] whileFalse: [
+		result := self
+			addProperty: self parseProperty
+			to: result.
+		(self match: '}')
+			ifTrue: [ ^ result ].
+		self expect: ',' ].
+	self error: 'end of object expected'
+!
+
+parseValue
+	| char |
+	stream atEnd ifFalse: [ 
+		char := stream peek.
+		char = ${
+			ifTrue: [ ^ self parseObject ].
+		char = $[
+			ifTrue: [ ^ self parseArray ].
+		char = $"
+			ifTrue: [ ^ self parseString ].
+		(char = $- or: [ char between: $0 and: $9 ])
+			ifTrue: [ ^ self parseNumber ].
+		(self match: 'true')
+			ifTrue: [ ^ self createTrue ].
+		(self match: 'false')
+			ifTrue: [ ^ self createFalse ].
+		(self match: 'null')
+			ifTrue: [ ^ self createNull ] ].
+	self error: 'invalid input'
+! !
+
+!CypressJsonParser methodsFor:'parsing-internal'!
+
+parseCharacter
+	| char |
+	(char := stream next) = $\ 
+		ifFalse: [ ^ char ].
+	(char := stream next) = $" 
+		ifTrue: [ ^ char ].
+	char = $\
+		ifTrue: [ ^ char ].
+	char = $/
+		ifTrue: [ ^ char ].
+	char = $b
+		ifTrue: [ ^ Character backspace ].
+	char = $f
+		ifTrue: [ ^ Character newPage ].
+	char = $n
+		ifTrue: [ ^ Character lfCharacter ].
+	char = $r
+		ifTrue: [ ^ Character crCharacter ].
+	char = $t
+		ifTrue: [ ^ Character tab ].
+	char = $u
+		ifTrue: [ ^ self parseCharacterHex ].
+	self error: 'invalid escape character \' , (String with: char)
+!
+
+parseCharacterHex
+	| value |
+	value := self parseCharacterHexDigit.
+	3 timesRepeat: [ value := (value << 4) + self parseCharacterHexDigit ].
+	^ Character unicodeCodePoint: value
+!
+
+parseCharacterHexDigit
+	| digit |
+	stream atEnd ifFalse: [
+		digit _ stream next asUppercase digitValue.
+		"accept hex digits"
+		(digit >= 0 and: [ digit < 16 ]) ifTrue: [ ^ digit ]].
+	self error: 'hex-digit expected'.
+!
+
+parseNumber
+	| negated number |
+	negated := stream peek = $-.
+	negated ifTrue: [ stream next ].
+	number := self parseNumberInteger.
+	(stream peek = $.) ifTrue: [
+		stream next. 
+		number := number + self parseNumberFraction ].
+	(stream peek = $e or: [ stream peek = $E ]) ifTrue: [
+		stream next.
+		number := number * self parseNumberExponent ].
+	negated ifTrue: [ number := number negated ].
+	^ self whitespace; createNumber: number
+!
+
+parseNumberExponent
+    | number negated |
+    number := 0.
+    negated := stream peek = $-.
+    (negated or: [ stream peek = $+ ])
+        ifTrue: [ stream next ].
+    [ stream atEnd not and: [ stream peek isDigit ] ] whileTrue: [ number := 10 * number + (stream next digitValue) ].
+    negated
+        ifTrue: [ number := number negated ].
+    ^ 10 raisedTo: number
+!
+
+parseNumberFraction
+    | number power |
+    number := 0.
+    power := 1.0.
+    [ stream atEnd not and: [ stream peek isDigit ] ]
+        whileTrue: [ 
+            number := 10 * number + (stream next digitValue).
+            power := power * 10.0 ].
+    ^ number / power
+!
+
+parseNumberInteger
+    | number |
+    number := 0.
+    [ stream atEnd not and: [ stream peek isDigit ] ] whileTrue: [ number := 10 * number + (stream next asciiValue - 48) ].
+    ^ number
+!
+
+parseProperty
+	| name value |
+	name := self parseString.
+	self expect: ':'.
+	value := self parseValue.
+	^ self createProperty: name with: value.
+!
+
+parseString
+	| result |
+	self expect: '"'.
+	result := WriteStream on: String new.
+	[ stream atEnd or: [ stream peek = $" ] ] 
+		whileFalse: [ result nextPut: self parseCharacter ].
+	^ self expect: '"'; createString: result contents
+! !
+
+!CypressJsonParser methodsFor:'private'!
+
+expect: aString
+	"Expects aString and consume input, throw an error otherwise."
+
+	^ (self match: aString) ifFalse: [ self error: aString , ' expected' ]
+!
+
+match: aString
+	"Tries to match aString, consume input and answer true if successful."
+	
+	| position |
+	position := stream position.
+	aString do: [ :each |
+		(stream atEnd or: [ stream next ~= each ]) ifTrue: [ 
+			stream position: position.
+			^ false ] ].
+	self whitespace.
+	^ true
+!
+
+whitespace
+	"Strip whitespaces from the input stream."
+
+	[ stream atEnd not and: [ stream peek isSeparator ] ]
+		whileTrue: [ stream next ]
+! !
+
+!CypressJsonParser class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressLoader.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,166 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressLoader
+	instanceVariableNames:'additions removals unloadable provisions errors methodAdditions
+		requirements'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressLoader comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressLoader class methodsFor:'loading'!
+
+updatePackage: aPackage withSnapshot: aSnapshot
+	self new
+		updatePackage: aPackage withSnapshot: aSnapshot;
+		load
+! !
+
+!CypressLoader methodsFor:'accessing'!
+
+additions
+
+	additions ifNil: [ additions := OrderedCollection new ].
+	^additions
+!
+
+errors
+	errors ifNil: [ errors := OrderedCollection new ].
+	^errors
+!
+
+methodAdditions
+
+	^#()
+!
+
+provisions
+	^ provisions ifNil: [provisions := (Smalltalk classes collect: [:cl | cl name]) asSet ]
+!
+
+removals
+
+	removals ifNil: [ removals := OrderedCollection new ].
+	^removals
+!
+
+unloadable
+
+	unloadable ifNil: [ unloadable := OrderedCollection new ].
+	^unloadable
+! !
+
+!CypressLoader methodsFor:'applying'!
+
+applyAddition: aCypressPatchOperation
+
+	self additions add: aCypressPatchOperation
+!
+
+applyModification: aCypressPatchOperation
+
+	self additions add: aCypressPatchOperation
+!
+
+applyRemoval: aCypressPatchOperation
+
+	self removals add: aCypressPatchOperation
+! !
+
+!CypressLoader methodsFor:'error handling'!
+
+handleErrorFor: aPatchOperation during: aBlock
+	aBlock on: Error do: [:ex | self errors add: aPatchOperation ].
+! !
+
+!CypressLoader methodsFor:'loading'!
+
+analyze
+
+	self 
+		analyzeAdditions;
+		analyzeRemovals
+!
+
+analyzeAdditions
+
+	| sorter |
+	sorter := CypressDependencySorter new 
+		addAll: self additions;
+		addExternalProvisions: self provisions;
+		yourself.
+	additions := sorter orderedItems.
+	requirements := sorter externalRequirements.
+	unloadable := sorter itemsWithMissingRequirements.
+!
+
+analyzeRemovals
+
+	| sorter |
+	sorter := CypressDependencySorter new 
+		addAll: self removals;
+		yourself.
+	removals := sorter orderedItems reversed.
+!
+
+basicLoad
+	errors := OrderedCollection new.
+	self additions do: [:ea | self loadClassDefinition: ea ]. "load class definitions first"
+	self additions do: [:ea | self loadMethodDefinition: ea ] . "load method definitions now"
+	self removals do: [:ea | self unloadDefinition: ea ]. "now we can remove things"
+	self errors do: [:ea | ea addMethodAdditionTo: methodAdditions]. "not sure about methodAddtions...yet"
+	self methodAdditions do: [:ea | self loadMethodAddition: ea ]. "ditto"
+	self additions do: [:ea | self postLoad: ea ]. "this is where the obsoletion is taken into account ..."
+!
+
+load
+
+	self analyze.
+	self unloadable isEmpty ifFalse: [self unloadableDefinitionsError].
+	self basicLoad
+!
+
+updatePackage: aPackage withSnapshot: aSnapshot
+	|  patch snapshot |
+	snapshot := aPackage snapshot.
+	patch := aSnapshot patchRelativeToBase: snapshot.
+	patch applyTo: self.
+	snapshot definitions do: [:ea | self provisions addAll: ea provisions]
+! !
+
+!CypressLoader methodsFor:'operations'!
+
+loadClassDefinition: aPatchOperation
+
+	self 
+		handleErrorFor: aPatchOperation 
+		during: [ aPatchOperation loadClassDefinition ]
+!
+
+loadMethodDefinition: aPatchOperation
+	
+	self 
+		handleErrorFor: aPatchOperation 
+		during: [ aPatchOperation loadMethodDefinition ]
+!
+
+postLoad: aPatchOperation
+	aPatchOperation postLoadDefinition
+!
+
+unloadDefinition: aPatchOperation
+	
+	self 
+		handleErrorFor: aPatchOperation 
+		during: [ aPatchOperation unloadDefinition ]
+! !
+
+!CypressLoader class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressLoaderTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,39 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressAbstractTest subclass:#CypressLoaderTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressLoaderTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressLoaderTest methodsFor:'running'!
+
+tearDown
+
+	| name |
+	super tearDown.
+	name := 'Cypress-Mocks'.
+	(CypressSnapshot definitions: self baseDefinitions)
+		 updatePackage: (CypressPackageDefinition new name: name)
+! !
+
+!CypressLoaderTest methodsFor:'testing'!
+
+testLoad
+
+	| name |
+	name := 'Cypress-Mocks'.
+	(CypressSnapshot definitions: self targetDefinitions)
+		 updatePackage: (CypressPackageDefinition new name: name)
+! !
+
+!CypressLoaderTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressMethodDefinition.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,218 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressDefinition subclass:#CypressMethodDefinition
+	instanceVariableNames:'classIsMeta source category selector className timeStamp'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressMethodDefinition comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressMethodDefinition class methodsFor:'instance creation'!
+
+className: aName
+classIsMeta: isMetaclass
+selector: aSelector
+category: aCategory
+source: aSource
+
+	^(self new)
+		className: aName
+		classIsMeta: isMetaclass
+		selector: aSelector
+		category: aCategory
+		source: aSource
+!
+
+className: aName
+classIsMeta: isMetaclass
+selector: aSelector
+category: aCategory
+source: aSource
+timeStamp: aTimeStamp
+
+	^(self new)
+		className: aName
+		classIsMeta: isMetaclass
+		selector: aSelector
+		category: aCategory
+		source: aSource
+		timeStamp: aTimeStamp
+! !
+
+!CypressMethodDefinition methodsFor:'accessing'!
+
+category
+
+	^category
+!
+
+classIsMeta
+
+	^classIsMeta
+!
+
+className
+
+	^className
+!
+
+description
+	^ Array	
+		with: className
+		with: selector
+		with: classIsMeta
+!
+
+selector
+
+	^selector
+!
+
+source
+
+	^source
+!
+
+timeStamp
+
+	^timeStamp
+! !
+
+!CypressMethodDefinition methodsFor:'comparing'!
+
+= aDefinition
+    ^ super = aDefinition
+        and: [ aDefinition source = self source
+                and: [ aDefinition category = self category ] ]
+!
+
+hash
+    | hash |
+    hash := String stringHash: classIsMeta asString initialHash: 0.
+    hash := String stringHash: source initialHash: hash.
+    hash := String stringHash: category initialHash: hash.
+    hash := String stringHash: className initialHash: hash.
+    ^ hash
+! !
+
+!CypressMethodDefinition methodsFor:'converting'!
+
+asCypressMethodDefinition
+
+	^self
+! !
+
+!CypressMethodDefinition methodsFor:'dependency'!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^{self className}
+! !
+
+!CypressMethodDefinition methodsFor:'initialization'!
+
+className: aName classIsMeta: isMetaclass selector: aSelector category: aCategory source: aSource
+
+	className := aName asSymbol.
+	classIsMeta := isMetaclass.
+	selector := aSelector asSymbol.
+	category := aCategory asSymbol.
+	source := aSource withLineEndings: String lfString.
+!
+
+className: aName classIsMeta: isMetaclass selector: aSelector category: aCategory source: aSource timeStamp: aTimeStamp
+
+	className := aName asSymbol.
+	classIsMeta := isMetaclass.
+	selector := aSelector asSymbol.
+	category := aCategory asSymbol.
+	source := aSource withLineEndings: String lfString.
+	timeStamp := aTimeStamp
+! !
+
+!CypressMethodDefinition methodsFor:'loading'!
+
+actualClass
+
+	| cls |
+	cls := self theNonMetaClass.
+	^self classIsMeta
+		ifTrue: [ cls class ]
+		ifFalse: [ cls  ].
+!
+
+loadMethodDefinition
+
+	self actualClass
+		compile: self source
+		classified: self category
+		withStamp: self timeStamp
+		notifying: nil.
+!
+
+postLoadOver: aDefinition
+
+	super postLoadOver: aDefinition.
+	(self isInitializer
+		and: [ aDefinition isNil or: [ self source ~= aDefinition source ]]) 
+			ifTrue: [ self theNonMetaClass initialize ].
+!
+
+theNonMetaClass
+	^Smalltalk at: self className
+!
+
+unloadDefinition
+
+	self actualClass removeSelector: self selector asSymbol
+! !
+
+!CypressMethodDefinition methodsFor:'printing'!
+
+printString
+
+	| str |
+	str := WriteStream on: String new.
+	str 
+		nextPutAll: super printString;
+		nextPutAll: ' (';
+		nextPutAll: self className.
+	self classIsMeta
+		ifTrue: [ str nextPutAll: ' class' ].
+	str 
+		nextPutAll: '>>';
+		nextPutAll: self selector;
+		nextPutAll: ')'.
+	^str contents
+! !
+
+!CypressMethodDefinition methodsFor:'testing'!
+
+isInitializer
+	^ self selector = 'initialize' and: [self classIsMeta]
+! !
+
+!CypressMethodDefinition methodsFor:'visiting'!
+
+classDefinition: classBlock methodDefinition: methodBlock
+
+	methodBlock value: self
+!
+
+instanceMethod: instanceBlock classMethod: classBlock
+
+	^(self classIsMeta
+		ifTrue: [ classBlock ]
+		ifFalse: [ instanceBlock ]) value: self
+! !
+
+!CypressMethodDefinition class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressMethodStructure.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,195 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressStructure subclass:#CypressMethodStructure
+	instanceVariableNames:'source isMetaclass classStructure timeStamp'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressMethodStructure comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressMethodStructure class methodsFor:'instance creation'!
+
+fromMethodDefinition: methodDefinition
+
+	^self new
+		fromMethodDefinition: methodDefinition;
+		yourself
+! !
+
+!CypressMethodStructure methodsFor:'accessing'!
+
+category
+
+	^self properties at: 'category'
+!
+
+category: aString
+
+	self properties at: 'category' put: aString
+!
+
+classStructure
+	^classStructure
+!
+
+classStructure: aCypressClassStructure
+	classStructure := aCypressClassStructure
+!
+
+cypressSource
+
+	| stream |
+	stream := WriteStream on: String new.
+	stream 
+		nextPutAll: self category;
+		newLine;
+		nextPutAll: self source.
+	^stream contents
+!
+
+isMetaclass
+
+	isMetaclass ifNil: [ isMetaclass := false ].
+	^isMetaclass
+!
+
+isMetaclass: aBoolean
+	isMetaclass := aBoolean
+!
+
+selector
+    ^ String
+        streamContents: [ :stream | 
+            self name
+                do: [ :chara | 
+                    stream
+                        nextPut:
+                            (chara = $.
+                                ifTrue: [ $: ]
+                                ifFalse: [ chara ]) ] ]
+!
+
+selector: aString
+    name := String
+        streamContents: [ :stream | 
+            aString
+                do: [ :chara | 
+                    stream
+                        nextPut:
+                            (chara = $:
+                                ifTrue: [ $. ]
+                                ifFalse: [ chara ]) ] ]
+!
+
+source
+
+	^source
+!
+
+source: aString
+
+	source := aString
+!
+
+timeStamp
+
+	^timeStamp
+!
+
+timeStamp: aTimeStamp
+
+	timeStamp := aTimeStamp
+! !
+
+!CypressMethodStructure methodsFor:'converting'!
+
+asCypressMethodDefinition
+
+	^CypressMethodDefinition 
+        	className: self classStructure className
+		classIsMeta: self isMetaclass
+		selector: self selector
+		category: self category
+		source: self source
+		timeStamp: self timeStamp
+! !
+
+!CypressMethodStructure methodsFor:'initialization'!
+
+fromJs: jsObject  named: methodNameParts
+
+	| ext |
+	(ext := methodNameParts at: 2) = '.st'
+		ifTrue: [  self extractCypressSource: (jsObject at: 'contents') ]
+		ifFalse: [ ext = '.json' ifTrue: [  properties := jsObject at: 'contents' ] ]
+!
+
+fromMethodDefinition: methodDefinition
+
+	self isMetaclass: methodDefinition classIsMeta.
+	self selector: methodDefinition selector.
+	self category: methodDefinition category.
+	self source: methodDefinition source.
+	self timeStamp: methodDefinition timeStamp.
+! !
+
+!CypressMethodStructure methodsFor:'private'!
+
+extractCypressSource: aString
+    | stream categoryStream sourceStream readingCategory |
+    stream := ReadStream on: aString.
+    categoryStream := WriteStream on: String new.
+    sourceStream := WriteStream on: String new.
+    readingCategory := true.
+    [ stream atEnd ]
+        whileFalse: [ 
+            | char |
+            char := stream next.
+            readingCategory
+                ifTrue: [ 
+                    char = Character lfCharacter
+                        ifTrue: [ readingCategory := false ]
+                        ifFalse: [ categoryStream nextPut: char ] ]
+                ifFalse: [ sourceStream nextPut: char ] ].
+    self category: categoryStream contents.
+    self source: sourceStream contents
+! !
+
+!CypressMethodStructure methodsFor:'writing'!
+
+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: ' }'
+! !
+
+!CypressMethodStructure class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressMockBasic.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,64 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressMockBasic
+	instanceVariableNames:'name'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Mocks'
+!
+
+CypressMockBasic class instanceVariableNames:'current'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
+CypressMockBasic comment:''
+!
+
+
+!CypressMockBasic class methodsFor:'initialization'!
+
+initialize
+	self current: self new
+! !
+
+!CypressMockBasic class methodsFor:'accessing'!
+
+current
+	^current
+!
+
+current: anObject
+	current := anObject
+! !
+
+!CypressMockBasic methodsFor:'accessing'!
+
+extra
+	"extra method"
+!
+
+name
+	^name
+!
+
+name: aString
+	name := aString
+! !
+
+!CypressMockBasic methodsFor:'initialization'!
+
+initialize
+	super initialize.
+	self name: 'Unknown'
+! !
+
+!CypressMockBasic class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
+
+CypressMockBasic initialize!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressModification.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,102 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressPatchOperation subclass:#CypressModification
+	instanceVariableNames:'obsoletion modification'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressModification comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressModification class methodsFor:'instance creation'!
+
+of: base to: target
+	^ self new base: base target: target
+! !
+
+!CypressModification methodsFor:'accessing'!
+
+description
+    ^ 'modify from: ' , self obsoletion printString , ' to: ' , self modification printString
+!
+
+modification
+
+	^modification
+!
+
+obsoletion
+
+	^obsoletion
+! !
+
+!CypressModification methodsFor:'applying'!
+
+applyTo: aCypressLoader
+
+	aCypressLoader applyModification: self
+! !
+
+!CypressModification methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	^self modification provisions
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^self modification requirements
+! !
+
+!CypressModification methodsFor:'initialization'!
+
+= aPatchOperation
+	^(super = aPatchOperation) and: [self obsoletion = aPatchOperation obsoletion and: [ self modification = aPatchOperation modification]]
+!
+
+base: base target: target
+
+	obsoletion := base.
+	modification := target.
+! !
+
+!CypressModification methodsFor:'loading'!
+
+loadClassDefinition
+
+	self modification loadClassDefinition
+!
+
+loadMethodDefinition
+	self modification loadMethodDefinition
+!
+
+postLoadDefinition
+	self modification postLoadOver: self obsoletion
+! !
+
+!CypressModification methodsFor:'printing'!
+
+printString
+
+	| str |
+	str := WriteStream on: String new.
+	str 
+		nextPutAll: super printString;
+		nextPutAll: ' (';
+		nextPutAll: self description;
+		nextPutAll: ')'.
+	^str contents
+! !
+
+!CypressModification class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPackageDefinition.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,84 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressPackageDefinition
+	instanceVariableNames:'name'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressPackageDefinition comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressPackageDefinition methodsFor:'accessing'!
+
+name
+	^ name
+!
+
+name: aString
+	name := aString
+! !
+
+!CypressPackageDefinition methodsFor:'comparing'!
+
+= other
+	^ other species = self species and: [other name sameAs: name]
+! !
+
+!CypressPackageDefinition methodsFor:'printing'!
+
+printString
+	^super printString, '(', name, ')'
+! !
+
+!CypressPackageDefinition methodsFor:'snapshotting'!
+
+snapshot
+    | package definitions map classMap |
+    package := CodePackage named: self name createIfAbsent: true registerIfNew: false.
+    definitions := OrderedCollection new.
+    (ChangeSet superclassOrder: package classes)
+        do: [ :cls | 
+            definitions add: cls asCypressClassDefinition.
+            (cls methodDictionary values asSortedCollection: [ :a :b | a selector <= b selector ])
+                do: [ :method | 
+                    (method category at: 1) = $*
+                        ifFalse: [ definitions add: method asCypressMethodDefinition ] ].
+            (cls class methodDictionary values asSortedCollection: [ :a :b | a selector <= b selector ])
+                do: [ :method | 
+                    (method category at: 1) = $*
+                        ifFalse: [ definitions add: method asCypressMethodDefinition ] ] ].
+    classMap := Dictionary new.
+    Smalltalk allClasses
+        do: [ :each | 
+            {each.
+            (each class)}
+                do: [ :aClass | 
+                    | defs |
+                    defs := OrderedCollection new.
+                    map := Dictionary new.
+                    aClass organization categories
+                        do: [ :category | 
+                            | methods |
+                            methods := aClass organization listAtCategoryNamed: category.
+                            (category asLowercase beginsWith: '*' , self name asLowercase)
+                                ifTrue: [ map at: category put: methods ] ].
+                    (map keys asSortedCollection: [ :a :b | a <= b ])
+                        do: [ :category | 
+                            ((map at: category) asSortedCollection: [ :a :b | a <= b ])
+                                do: [ :method | defs add: (aClass compiledMethodAt: method) asCypressMethodDefinition ] ].
+                    defs notEmpty
+                        ifTrue: [ classMap at: each put: defs ] ] ].
+    (ChangeSet superclassOrder: classMap keys) do: [ :aClass | definitions addAll: (classMap at: aClass) ].
+    ^ CypressSnapshot definitions: definitions
+
+    "Modified: / 30-08-2012 / 13:32:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CypressPackageDefinition class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPackageReader.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,193 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressPackageReader
+	instanceVariableNames:'packageDirectory packageStructure properties'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressPackageReader comment:'Reader for the Cypress multi-dialect file format for Smalltalk packages

	CypressPackageReader installAsCodePackage: (FileDirectory default directoryNamed: ''Cypress-Mocks.package'')'
+!
+
+
+!CypressPackageReader class methodsFor:'instance creation'!
+
+readPackageStructureFrom: aPackagesDirectory
+
+	^(self new)
+		packageDirectory: aPackagesDirectory;
+		read;
+		yourself
+! !
+
+!CypressPackageReader class methodsFor:'services'!
+
+installAsCodePackage: aCypressPackageDirectory
+	"
+	For example:
+		CypressPackageReader installAsCodePackage: (FileDirectory default directoryNamed: 'Cypress-Mocks.package')
+	"
+	| reader cypressStructure incomingSnapshot |
+	reader _ CypressPackageReader readPackageStructureFrom: aCypressPackageDirectory.
+	cypressStructure _ reader packageStructure.
+	incomingSnapshot _ cypressStructure snapshot.
+	incomingSnapshot updatePackage: (CypressPackageDefinition new name: cypressStructure packageName).
+	CodePackage named: cypressStructure packageName createIfAbsent: true registerIfNew: true
+! !
+
+!CypressPackageReader methodsFor:'accessing'!
+
+packageDirectory
+
+	^packageDirectory
+!
+
+packageDirectory: aDirectory
+
+	packageDirectory := aDirectory
+!
+
+packageStructure
+
+	^packageStructure
+!
+
+packageStructure: aPackageStructure
+
+	packageStructure := aPackageStructure
+! !
+
+!CypressPackageReader methodsFor:'private'!
+
+classStructureFrom: classPropertiesDict 
+
+	^(CypressClassStructure new)
+		isClassExtension: true;
+		properties: classPropertiesDict;
+		packageStructure: packageStructure;
+		yourself
+!
+
+classStructureFrom: classPropertiesDict comment: classComment.
+
+	^(self classStructureFrom: classPropertiesDict)
+		isClassExtension: false;
+		comment: classComment;
+		yourself
+! !
+
+!CypressPackageReader methodsFor:'reading'!
+
+read
+
+    	self readPropertiesFile.
+	self readPackageStructure
+!
+
+readClassStructureFromEntry: classEntry
+	| classDirectory methodPropertiesDict classPropertiesDict classComment entries classStructure |
+	classDirectory _ classEntry asFileDirectory.
+	entries _ classDirectory entries.
+	(entries
+		detect: [ :entry | entry name = 'methodProperties.json' ]
+		ifNone: [ ]) ifNotNil: [ :propertyEntry |
+		propertyEntry readStreamDo: [ :fileStream |
+			methodPropertiesDict _ CypressJsonParser parseStream: fileStream ]].
+	(entries
+		detect: [ :entry | entry name = 'properties.json' ]
+		ifNone: [ ]) ifNotNil: [ :propertyEntry |
+		propertyEntry readStreamDo: [ :fileStream |
+			classPropertiesDict _ CypressJsonParser parseStream: fileStream ]].
+	(entries
+		detect: [ :entry | entry name = 'README.md' ]
+		ifNone: [ ]) ifNotNil: [ :commentEntry |
+		commentEntry readStreamDo: [ :fileStream |
+			classComment _ fileStream contents ]].
+	classStructure _ self
+		classStructureFrom: classPropertiesDict
+		comment: classComment.
+	self
+		readMethodStructureFor: classStructure
+		in: entries
+		methodProperties: methodPropertiesDict.
+	^ classStructure.
+!
+
+readExtensionClassStructureFromEntry: classEntry
+	| classDirectory methodPropertiesDict classPropertiesDict entries classStructure |
+	classDirectory _ classEntry asFileDirectory.
+	entries _ classDirectory entries.
+	(entries
+		detect: [ :entry | entry name = 'methodProperties.json' ]
+		ifNone: [ ]) ifNotNil: [ :propertyEntry |
+		propertyEntry readStreamDo: [ :fileStream |
+			methodPropertiesDict _ CypressJsonParser parseStream: fileStream ]].
+	(entries
+		detect: [ :entry | entry name = 'properties.json' ]
+		ifNone: [ ]) ifNotNil: [ :propertyEntry |
+		propertyEntry readStreamDo: [ :fileStream |
+			classPropertiesDict _ CypressJsonParser parseStream: fileStream ]].
+	classStructure _ self classStructureFrom: classPropertiesDict.
+	self
+		readMethodStructureFor: classStructure
+		in: entries
+		methodProperties: methodPropertiesDict.
+	^ classStructure
+!
+
+readMethodStructureFor: classStructure in: entries methodProperties: methodPropertiesDict
+	entries do: [ :entry | | methods isMeta |
+		isMeta _ false.
+		methods _ entry name = 'class'
+			ifTrue: [
+				isMeta _ true.
+				classStructure classMethods ]
+			ifFalse: [ classStructure instanceMethods ].
+		(entry name = 'instance' or: [ entry name = 'class' ]) ifTrue: [
+			(entry asFileDirectory entries select: [ :each |
+				each name first ~= $. and: [ each name endsWith: '.st' ]]) do: [ :methodEntry |
+				methodEntry readStreamDo: [ :fileStream | | category source selector timeStamp |
+					category _ fileStream nextLine.
+					source _ fileStream upToEnd.
+					selector _ Parser new parseSelector: source.
+					timeStamp _ (methodPropertiesDict
+						at: (isMeta ifTrue: ['class'] ifFalse: ['instance']))
+						at: selector.
+					methods
+						at: selector
+						put:
+							(CypressMethodStructure new
+								 classStructure: classStructure;
+								 name: selector;
+								 isMetaclass: isMeta;
+								 selector: selector;
+								 category: category;
+								 source: source;
+								 timeStamp: timeStamp
+								 yourself) ]]]]
+!
+
+readPackageStructure
+	packageStructure _ CypressPackageStructure new name: self packageDirectory localName.
+	self packageDirectory entries do: [ :entry |
+		entry name first ~= $. ifTrue: [
+			(entry name endsWith: '.class') ifTrue: [
+				self packageStructure classes add: (self readClassStructureFromEntry: entry) ].
+			(entry name endsWith: '.extension') ifTrue: [
+				self packageStructure extensions add: (self readExtensionClassStructureFromEntry: entry) ]]]
+!
+
+readPropertiesFile	
+
+	self packageDirectory 
+		readOnlyFileNamed: 'properties.json'
+		do: [:fileStream |
+			properties := CypressJsonParser parseStream: fileStream ]
+! !
+
+!CypressPackageReader class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPackageStructure.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,192 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressStructure subclass:#CypressPackageStructure
+	instanceVariableNames:'classes extensions'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressPackageStructure comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressPackageStructure class methodsFor:'instance creation'!
+
+fromJson: aJsonString
+
+	^self fromJs: (CypressJsonParser parse: aJsonString)
+!
+
+fromPackage: aCypressPackageDefinition
+
+	^(self new) 
+		fromPackage: aCypressPackageDefinition;
+		yourself
+! !
+
+!CypressPackageStructure methodsFor:'accessing'!
+
+classes
+
+	classes ifNil: [ classes := OrderedCollection new ].
+	^classes
+!
+
+extensions
+
+	extensions ifNil: [ extensions := OrderedCollection new ].
+	^extensions
+!
+
+packageExtension
+
+	^self properties at: 'extension' ifAbsent: ['.package' ]
+!
+
+packageName
+
+	^self name copyFrom: 1 to: (self name size - self packageExtension size)
+!
+
+packageStructure
+	^self
+! !
+
+!CypressPackageStructure methodsFor:'initialization'!
+
+fromJs: jsObject
+
+	name := jsObject at: 'name'.
+	(jsObject at: 'contents') do: [:jsClassObject| | classStructure objectName |
+		classStructure := (CypressClassStructure new)
+                		packageStructure: self;
+				yourself.
+                (  '*.extension' match:(objectName := jsClassObject at: 'name') )
+			ifTrue: [ 
+				classStructure isClassExtension: true.
+				self extensions add: classStructure ]
+			ifFalse: [
+				( '*.class' match: objectName)
+					ifTrue: [ 
+						classStructure isClassExtension: false.
+						self classes add: classStructure ]].
+		classStructure fromJs: jsClassObject].
+	properties := jsObject at: 'properties.json'
+!
+
+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 ].
+! !
+
+!CypressPackageStructure methodsFor:'snapshotting'!
+
+snapshot
+        | definitions |
+        definitions := OrderedCollection new.
+        self classes do: [:classStructure |
+                definitions add: classStructure asCypressClassDefinition.
+                (classStructure instanceMethods values asArray asSortedCollection: [:a :b | a selector <= b selector]) do: [:methodStructure |
+                        definitions add: methodStructure asCypressMethodDefinition ].
+                (classStructure classMethods values asArray asSortedCollection: [:a :b | a selector <= b selector]) do: [:methodStructure |
+                        definitions add: methodStructure asCypressMethodDefinition ]].
+        self extensions do: [:classStructure |
+                (classStructure instanceMethods values asArray asSortedCollection: [:a :b | a selector <= b selector]) do: [:methodStructure |
+                        definitions add: methodStructure asCypressMethodDefinition ].
+                (classStructure classMethods values asArray asSortedCollection: [:a :b | a selector <= b selector]) do: [:methodStructure |
+                        definitions add: methodStructure asCypressMethodDefinition ]].
+        ^ CypressSnapshot definitions: definitions
+
+    "Modified: / 30-08-2012 / 13:31:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CypressPackageStructure methodsFor:'writing'!
+
+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: '}'
+! !
+
+!CypressPackageStructure class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPackageWriter.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,270 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressPackageWriter
+	instanceVariableNames:'packageStructure rootDirectory packageDirectory'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressPackageWriter class instanceVariableNames:'specials'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
+CypressPackageWriter comment:''
+!
+
+
+!CypressPackageWriter class methodsFor:'instance creation'!
+
+writePackageStructure: aPackageStructure to: aPackagesDirectory
+
+	self new
+		packageStructure: aPackageStructure;
+		rootDirectory: aPackagesDirectory;
+		write
+! !
+
+!CypressPackageWriter class methodsFor:'as yet unclassified'!
+
+initializeSpecials
+    | map |
+    map := Dictionary new.
+    map
+        at: $+ put: 'plus';
+        at: $- put: 'minus';
+        at: $= put: 'equals';
+        at: $< put: 'less';
+        at: $> put: 'more';
+        at: $% put: 'percent';
+        at: $& put: 'and';
+        at: $| put: 'pipe';
+        at: $* put: 'star';
+        at: $/ put: 'slash';
+        at: $\ put: 'backslash';
+        at: $~ put: 'tilde';
+        at: $? put: 'wat';
+        at: $@ put: 'at'.
+    map keys do: [ :key | map at: (map at: key) put: key ].
+    ^ map
+!
+
+specials
+    ^ specials ifNil: [ specials := self initializeSpecials ]
+! !
+
+!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
+! !
+
+!CypressPackageWriter methodsFor:'accessing'!
+
+packageDirectory
+
+	packageDirectory 
+		ifNil: [ 
+			packageDirectory := self rootDirectory directoryNamed: self packageStructure name.
+			packageDirectory assureExistence ].
+	^packageDirectory
+!
+
+packageDirectory: aPackageDirectory
+
+	packageDirectory := aPackageDirectory
+!
+
+packageStructure
+
+	^packageStructure
+!
+
+packageStructure: aCypressPackageStructure
+
+	packageStructure := aCypressPackageStructure
+!
+
+rootDirectory
+
+	^rootDirectory
+!
+
+rootDirectory: aDirectory
+
+	rootDirectory := aDirectory
+! !
+
+!CypressPackageWriter methodsFor:'private'!
+
+directoryForDirectoryNamed: directoryNameOrPath
+    ^ directoryNameOrPath = '.'
+        ifTrue: [ self packageDirectory assureExistence ]
+        ifFalse: [ | dir |
+            dir := self packageDirectory directoryNamed: directoryNameOrPath.
+            dir assureExistence.
+            dir  ]
+!
+
+fileNameForSelector: selector
+    ^ selector last = $:
+        ifTrue: [ 
+            selector
+                collect: [ :each | 
+                    each = $:
+                        ifTrue: [ $. ]
+                        ifFalse: [ each ] ] ]
+        ifFalse: [ 
+            selector first isLetter
+                ifTrue: [ selector ]
+                ifFalse: [ 
+                    | output specials |
+                    specials := self class specials.
+                    output := String new writeStream.
+                    output nextPut: $^.
+                    selector do: [ :each | output nextPutAll: (specials at: each) ] separatedBy: [ output nextPut: $. ].
+                    output contents ] ]
+!
+
+writeInDirectoryName: directoryNameOrPath fileName: fileName extension: ext visit: visitBlock
+    | directory |
+    directory := self directoryForDirectoryNamed: directoryNameOrPath.
+    directory
+        forceNewFileNamed: fileName , ext
+        do: [ :file |
+            visitBlock value: file ]
+! !
+
+!CypressPackageWriter methodsFor:'writing'!
+
+write
+
+	self packageDirectory exists
+        ifTrue: [ self packageDirectory recursiveDelete ].
+    	self writePropertiesFile.
+	self writePackageStructure
+!
+
+writeClassComment: classStructure on: fileStream
+
+    fileStream nextPutAll: (classStructure comment withLineEndings: String lfString)
+!
+
+writeClassStructure: classStructure on: fileStream
+
+    | properties |
+    properties := Dictionary new.
+    properties at: 'name' put: classStructure className.
+    properties at: 'super' put: classStructure superclassName.
+    properties at: 'instvars' put: classStructure instanceVariableNames.
+    properties at: 'classinstvars' put: classStructure classInstanceVariableNames.
+    properties writeCypressJsonOn: fileStream forHtml: true indent: 0
+!
+
+writeClassStructure: classStructure to: classPath
+
+    self
+        writeInDirectoryName: classPath
+        fileName: 'README'
+        extension: '.md'
+        visit: [:fileStream | self writeClassComment: classStructure on: fileStream ].
+    self
+        writeInDirectoryName: classPath
+        fileName: 'properties'
+        extension: '.json'
+        visit: [:fileStream | self writeClassStructure: classStructure on: fileStream ]
+!
+
+writeExtensionClassStructure: classStructure to: classPath
+
+     self
+        writeInDirectoryName: classPath
+        fileName: 'properties'
+        extension: '.json'
+        visit: [:fileStream |  | properties |
+    		properties := Dictionary new.
+    		properties at: 'name' put: classStructure className.
+    		properties writeCypressJsonOn: fileStream forHtml: true indent: 0 ]
+!
+
+writeMethodStructure: methodStructure to:methodPath
+
+    | filename |
+    filename := self fileNameForSelector: methodStructure selector.
+    self
+        writeInDirectoryName: methodPath
+        fileName: filename
+        extension: '.st'
+        visit: [:fileStream |
+		fileStream
+        		nextPutAll: methodStructure category;
+        		newLine;
+        		nextPutAll: (methodStructure source withLineEndings: String lfString) ]
+!
+
+writePackageStructure
+
+	self writePackageStructureClasses:  self packageStructure classes isClassExtension: false.
+	self writePackageStructureClasses:  self packageStructure extensions isClassExtension: true
+!
+
+writePackageStructureClasses: classStructures isClassExtension: isClassExtension
+	| classDirExtension methodProperties classMethodsMap instanceMethodMap |
+	classDirExtension _ isClassExtension
+		ifTrue: [ '.extension' ]
+		ifFalse: [ '.class' ].
+	classStructures do: [ :classStructure | | classPath instanceMethodPath classMethodPath |
+		classPath _ classStructure className , classDirExtension , FileDirectory slash.
+		isClassExtension
+			ifTrue: [
+				self writeExtensionClassStructure: classStructure to: classPath ]
+			ifFalse: [
+				self writeClassStructure: classStructure to: classPath ].
+		methodProperties _ Dictionary new.
+		instanceMethodPath _ classPath , 'instance' , FileDirectory slash.
+		methodProperties at: 'instance' put: (instanceMethodMap _ Dictionary new).
+		classStructure instanceMethods do: [ :methodStructure |
+			self writeMethodStructure: methodStructure to: instanceMethodPath.
+			instanceMethodMap
+				at: methodStructure selector asString
+				put: methodStructure timeStamp ].
+		classMethodPath _ classPath , 'class' , FileDirectory slash.
+		methodProperties at: 'class' put: (classMethodsMap _ Dictionary new).
+		classStructure classMethods do: [ :methodStructure |
+			self writeMethodStructure: methodStructure to: classMethodPath.
+			classMethodsMap
+				at: methodStructure selector asString
+				put: methodStructure timeStamp ].
+		self
+			writeInDirectoryName: classPath
+			fileName: 'methodProperties'
+			extension: '.json'
+			visit: [ :fileStream | methodProperties writeCypressJsonOn: fileStream forHtml: false indent: 0 ]]
+!
+
+writePropertiesFile
+
+    self
+        writeInDirectoryName: '.'
+        fileName: 'properties'
+        extension: '.json'
+        visit: [:fileStream | Dictionary new writeCypressJsonOn: fileStream forHtml: true indent: 0 ]
+! !
+
+!CypressPackageWriter class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPatch.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,62 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressPatch
+	instanceVariableNames:'operations'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressPatch comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressPatch class methodsFor:'instance creation'!
+
+fromBase: baseSnapshot toTarget: targetSnapshot
+	^ (self new)
+		fromBase: baseSnapshot
+		toTarget: targetSnapshot
+! !
+
+!CypressPatch methodsFor:'accessing'!
+
+operations
+
+	^operations
+! !
+
+!CypressPatch methodsFor:'applying'!
+
+applyTo: aCypressLoader
+	operations do: [:ea | ea applyTo: aCypressLoader].
+! !
+
+!CypressPatch methodsFor:'initialization'!
+
+fromBase: baseSnapshot toTarget: targetSnapshot
+	| base target |	
+	operations := OrderedCollection new.
+	base := CypressDefinitionIndex definitions: baseSnapshot definitions.
+	target := CypressDefinitionIndex definitions: targetSnapshot definitions.
+	
+	target definitions do:
+		[:t |
+		base
+			definitionLike: t
+			ifPresent: [:b | (b isSameRevisionAs: t) ifFalse: [operations add: (CypressModification of: b to: t)]]
+			ifAbsent: [operations add: (CypressAddition of: t)]].
+		
+	base definitions do:
+		[:b |
+		target
+			definitionLike: b
+			ifPresent: [:t | ]
+			ifAbsent: [operations add: (CypressRemoval of: b)]]
+! !
+
+!CypressPatch class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPatchOperation.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,76 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressPatchOperation
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressPatchOperation comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressPatchOperation methodsFor:'accessing'!
+
+description
+
+	self subclassResponsibility
+! !
+
+!CypressPatchOperation methodsFor:'applying'!
+
+applyTo: aCypressLoader
+
+	self subclassResponsibility
+! !
+
+!CypressPatchOperation methodsFor:'comparing'!
+
+= aPatchOperation
+	^aPatchOperation isKindOf: self class
+!
+
+hash
+    ^ self description hash
+! !
+
+!CypressPatchOperation methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	self subclassResponsibility
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	self subclassResponsibility
+! !
+
+!CypressPatchOperation methodsFor:'loading'!
+
+loadClassDefinition
+
+	self subclassResponsibility
+!
+
+loadMethodDefinition
+	self subclassResponsibility
+!
+
+postLoadDefinition
+	self subclassResponsibility
+!
+
+unloadDefinition
+
+	self error: 'inappropriate to send #unloadDefinition to an addition or modification operation'
+! !
+
+!CypressPatchOperation class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressPatchTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,86 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressAbstractTest subclass:#CypressPatchTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressPatchTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressPatchTest methodsFor:'testing'!
+
+testDictionaryOfPatchOperations
+	"loader uses dictionary for managing patch operations ... ensure that Amber Dictionaries stand up"
+
+	| dict |
+	dict := Dictionary new.
+	self baseTargetPatch do: [:each | 
+		dict at: each put: each ].
+	self baseTargetPatch do: [:each | 
+		self assert: (dict at: each) = each ].
+!
+
+testPatch
+    | baseSnapshot targetSnapshot patch operations expected |
+    baseSnapshot := CypressSnapshot definitions: self baseDefinitions.
+    targetSnapshot := CypressSnapshot definitions: self targetDefinitions.
+    patch := CypressPatch fromBase: baseSnapshot toTarget: targetSnapshot.
+    operations := patch operations.
+    self assert: operations size = 4.
+    expected := self baseTargetPatch asArray.
+    1 to: operations size do: [ :index | 
+        | op |
+        op := operations at: index.
+        self assert: (expected includes: op) ]
+!
+
+testPatchOperationEquality
+
+	| className modification removal addition |
+	className := 'CypressMockBasic'.
+	modification := CypressModification 
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'name:'
+        			category: 'accessing'
+        			source:'name: aString
+	name := aString') 
+			to: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'name:'
+        			category: 'accessing'
+        			source:'name: aString
+	"changed method"
+	name := aString').
+	self assert: modification = modification.
+	removal := CypressRemoval 
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'extra'
+        			category: 'accessing'
+        			source:'extra
+	"extra method"').
+	self assert: removal = removal.
+	addition := CypressAddition
+			of: (CypressMethodDefinition
+          			className: className
+        			classIsMeta: false
+        			selector: 'extra'
+        			category: 'accessing'
+        			source:'extra
+	"extra method"').
+	self assert: addition = addition.
+! !
+
+!CypressPatchTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressRemoval.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,106 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressPatchOperation subclass:#CypressRemoval
+	instanceVariableNames:'definition'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressRemoval comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressRemoval class methodsFor:'instance creation'!
+
+of: aDefinition
+	^ self new definition: aDefinition
+! !
+
+!CypressRemoval methodsFor:'accessing'!
+
+definition
+
+	^definition
+!
+
+description
+
+	^'remove: ', self definition printString
+! !
+
+!CypressRemoval methodsFor:'applying'!
+
+applyTo: aCypressLoader
+
+	aCypressLoader applyRemoval: self
+! !
+
+!CypressRemoval methodsFor:'comparing'!
+
+= aPatchOperation
+	^(super = aPatchOperation) and: [self definition = aPatchOperation definition]
+! !
+
+!CypressRemoval methodsFor:'dependency'!
+
+provisions
+	"Answer list of global names defined by this definition"
+
+	^#()
+!
+
+requirements
+	"Answer list of global names required by this definition"
+
+	^#()
+! !
+
+!CypressRemoval methodsFor:'initialization'!
+
+definition: aDefinition
+
+	definition := aDefinition
+! !
+
+!CypressRemoval methodsFor:'loading'!
+
+loadClassDefinition
+	
+	self error: 'inappropriate to send #loadClassDefinition to a removal operation'
+!
+
+loadMethodDefinition
+	
+	self error: 'inappropriate to send #loadMethodDefinition to a removal operation'
+!
+
+postLoadDefinition
+	
+	self error: 'inappropriate to send #postLoadDefinition to a removal operation'
+!
+
+unloadDefinition
+
+	self definition unloadDefinition
+! !
+
+!CypressRemoval methodsFor:'printing'!
+
+printString
+
+	| str |
+	str := WriteStream on: String new.
+	str 
+		nextPutAll: super printString;
+		nextPutAll: ' (';
+		nextPutAll: self description;
+		nextPutAll: ')'.
+	^str contents
+! !
+
+!CypressRemoval class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressSnapshot.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,63 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressSnapshot
+	instanceVariableNames:'definitions'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Definitions'
+!
+
+CypressSnapshot comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressSnapshot class methodsFor:'instance creation'!
+
+definitions: aDefinitions
+
+	^(self new) definitions: aDefinitions
+! !
+
+!CypressSnapshot methodsFor:'accessing'!
+
+definitions
+
+	^definitions
+!
+
+definitions: aDefinitions
+
+	definitions := aDefinitions
+! !
+
+!CypressSnapshot methodsFor:'comparing'!
+
+= other
+	^ definitions asArray = other definitions asArray
+! !
+
+!CypressSnapshot methodsFor:'enumerating'!
+
+classDefinitions: classBlock methodDefinitions: methodBlock
+
+	self definitions do: [:definition |
+		definition classDefinition: classBlock methodDefinition: methodBlock]
+! !
+
+!CypressSnapshot methodsFor:'loading'!
+
+updatePackage: aPackage
+	CypressLoader updatePackage: aPackage withSnapshot: self
+! !
+
+!CypressSnapshot methodsFor:'patching'!
+
+patchRelativeToBase: aSnapshot
+	^ CypressPatch fromBase: aSnapshot toTarget: self
+! !
+
+!CypressSnapshot class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressSnapshotTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,36 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressAbstractTest subclass:#CypressSnapshotTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressSnapshotTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressSnapshotTest methodsFor:'testing'!
+
+testSnapshot
+	| name pkg  |
+	name := 'Cypress-Mocks'.
+	pkg := CypressPackageDefinition new name: name.
+	self validatePackage: pkg against: self baseDefinitions
+!
+
+testSnapshotEquality
+	| name pkg packageDefinitions expectedDefinitions |
+	name := 'Cypress-Mocks'.
+	pkg := CypressPackageDefinition new name: name.
+	packageDefinitions := pkg snapshot definitions.
+	expectedDefinitions := self baseDefinitions.
+	self assert: packageDefinitions asArray = expectedDefinitions asArray
+! !
+
+!CypressSnapshotTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressStructure.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,125 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+Object subclass:#CypressStructure
+	instanceVariableNames:'name properties packageStructure'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Structure'
+!
+
+CypressStructure comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressStructure class methodsFor:'instance creation'!
+
+fromJs: jsObject
+
+	^(self new) 
+		fromJs: jsObject asCypressPropertyObject;
+		yourself
+! !
+
+!CypressStructure methodsFor:'accessing'!
+
+name
+
+	^name
+!
+
+name: aString 
+
+	name := aString
+!
+
+packageStructure
+	^packageStructure
+!
+
+packageStructure: aCypressPackageStructure
+	packageStructure := aCypressPackageStructure
+!
+
+properties
+
+	properties ifNil: [ properties := Dictionary new ].
+	^properties
+! !
+
+!CypressStructure methodsFor:'initialization'!
+
+fromJs: jsObject
+
+	self subclassResponsibility
+!
+
+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 ].
+! !
+
+!CypressStructure methodsFor:'writing'!
+
+path: aFSPath file: aFilename write: writeBlock
+
+	| fs stream |
+	fs := aFSPath fs.
+	stream := fs createWriteStream: (aFSPath resolve: aFilename).
+	writeBlock value: stream.
+	stream end.
+!
+
+writeJsonOn: aStream
+
+	self writeJsonOn: aStream indent: 0.
+!
+
+writeJsonOn: aStream  indent: indent
+
+	self subclassResponsibility
+! !
+
+!CypressStructure class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CypressStructureTest.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,111 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+CypressAbstractTest subclass:#CypressStructureTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Cypress-Tests'
+!
+
+CypressStructureTest comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
+!
+
+
+!CypressStructureTest methodsFor:'tests'!
+
+testClassStructure
+
+	| jsObject packageStructure classStructure classProperties |
+	jsObject := self compileJSON: self basePackageStructureJson.
+	packageStructure := CypressPackageStructure fromJs: jsObject.
+	classStructure := packageStructure classes first.
+	self assert: classStructure name = 'CypressMockBasic'.
+	self deny: classStructure isClassExtension.
+	self assert: classStructure comment =  'This mock contains basic class and instance method selectors'..
+	classProperties := classStructure properties.
+	self assert: classProperties size = 4.
+	self assert: (classProperties at: 'instvars') = #('name').
+	self assert: (classProperties at: 'classinstvars') = #('current').
+	self assert: (classProperties at: 'name') = 'CypressMockBasic'.
+	self assert: (classProperties at: 'super') = 'Object'.
+	self assert: classStructure instanceMethods size = 4.
+	self assert: classStructure classMethods size = 3.
+	classStructure := packageStructure extensions first.
+	self assert: classStructure name = 'Object'.
+	self assert: classStructure isClassExtension.
+	self assert: classStructure comment = ''.
+	classProperties := classStructure properties.
+	self assert: classProperties size = 1.
+	self assert: (classProperties at: 'name') = 'Object'.
+	self assert: classStructure instanceMethods size = 1.
+	self assert: classStructure classMethods size = 0.
+!
+
+testJson
+	"Let's compile the JSON without errors"
+
+	self compileJSON: self basePackageStructureJson
+!
+
+testPackageStructureFromJson
+
+	| packageStructure classStructure classProperties |
+	packageStructure := CypressPackageStructure fromJson: self basePackageStructureJson.
+	self assert: packageStructure name = 'Cypress-Mocks.package'.
+	self assert: packageStructure packageName = 'Cypress-Mocks'.
+	self assert: packageStructure properties isEmpty.
+	self assert: packageStructure extensions size = 1.
+	self assert: packageStructure classes size = 1.
+!
+
+testPackageStructureFromPackage
+
+	| packageStructure |
+	packageStructure := CypressPackageStructure fromPackage: (CypressPackageDefinition new name: 'Cypress-Mocks').
+	self validatePackage: packageStructure against: self baseDefinitions
+!
+
+testPackageStructureSnapshot
+
+	| packageStructure |
+	packageStructure := CypressPackageStructure fromJs: (self compileJSON: self basePackageStructureJson).
+	self validatePackage: packageStructure against: self baseDefinitions
+!
+
+testPackageStructureToJson
+
+	| packageStructure stream json |
+	packageStructure := CypressPackageStructure fromPackage: (CypressPackageDefinition new name: 'Cypress-Mocks').
+	stream := WriteStream on: String new.
+	packageStructure writeJsonOn: stream.
+	json := stream contents.
+	self assert: (self basePackageStructureJson withLineEndings: String lfString) = (json withLineEndings: String lfString)
+!
+
+testPropertyDictionaryRead
+
+	| propertyDictionary phoneNumbers |
+	propertyDictionary := (self compileJSON: self sampleJson) asCypressPropertyObject.
+	self assert: (propertyDictionary at: 'name') = 'John Smith'.
+	self assert: (propertyDictionary at: 'age') = 25.
+	self assert: (propertyDictionary at: 'registered').
+	phoneNumbers := propertyDictionary at: 'phoneNumber'.
+	self assert: phoneNumbers size = 2.
+	self assert: ((phoneNumbers at: 1) at: 'number') = '212 555-1234'.
+	self assert: ((phoneNumbers at: 2) at: 'number') = '646 555-4567'.
+!
+
+testPropertyDictionaryWrite
+
+	| propertyDictionary stream x y |
+	propertyDictionary := (self compileJSON: self sampleJson) asCypressPropertyObject.
+	stream := WriteStream on: String new.
+	propertyDictionary writeCypressJsonOn: stream forHtml: true indent: 0.
+	self assert: (x:= stream contents withLineEndings: String lfString)  = (y := self sampleJson withLineEndings: String lfString)
+! !
+
+!CypressStructureTest class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Make.proto	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,168 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: stx_goodies_cypress.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# The Makefile as generated by this Make.proto supports the following targets:
+#    make         - compile all st-files to a classLib
+#    make clean   - clean all temp files
+#    make clobber - clean all
+#
+# This file contains definitions for Unix based platforms.
+# It shares common definitions with the win32-make in Make.spec.
+
+#
+# position (of this package) in directory hierarchy:
+# (must point to ST/X top directory, for tools and includes)
+TOP=../..
+INCLUDE_TOP=$(TOP)/..
+
+# subdirectories where targets are to be made:
+SUBDIRS=
+
+
+# subdirectories where Makefiles are to be made:
+# (only define if different from SUBDIRS)
+# ALLSUBDIRS=
+
+REQUIRED_SUPPORT_DIRS=
+
+# if your embedded C code requires any system includes,
+# add the path(es) here:,
+# ********** OPTIONAL: MODIFY the next lines ***
+# LOCALINCLUDES=-Ifoo -Ibar
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/monticello -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic2 -I$(INCLUDE_TOP)/stx/libcompat -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libcomp -I$(INCLUDE_TOP)/stx/libhtml
+
+
+# if you need any additional defines for embedded C code,
+# add them here:,
+# ********** OPTIONAL: MODIFY the next lines ***
+# LOCALDEFINES=-Dfoo -Dbar -DDEBUG
+LOCALDEFINES=
+
+LIBNAME=libstx_goodies_cypress
+STCLOCALOPT='-package=$(PACKAGE)' -I. $(LOCALINCLUDES) $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) -headerDir=.  -varPrefix=$(LIBNAME)
+
+
+# ********** OPTIONAL: MODIFY the next line ***
+# additional C-libraries that should be pre-linked with the class-objects
+LD_OBJ_LIBS=
+LOCAL_SHARED_LIBS=
+
+
+# ********** OPTIONAL: MODIFY the next line ***
+# additional C targets or libraries should be added below
+LOCAL_EXTRA_TARGETS=
+
+OBJS= $(COMMON_OBJS) $(UNIX_OBJS)
+
+
+
+all:: preMake classLibRule postMake
+
+pre_objs::  
+
+
+
+
+# Update SVN revision in stx_libbasic3.st
+ifneq (,$(findstring .svn,$(wildcard .svn)))
+.svnversion: *.st
+	if [ -d .svn ]; then \
+		rev=$(shell svnversion -n); \
+		echo -n $$rev > .svnversion; \
+	else \
+		echo -n exported > .svnversion; \
+	fi
+
+stx_goodies_cypress.o: stx_goodies_cypress.st .svnversion 
+	@if [ -d .svn ]; then \
+		rev2="$(shell printf "%-16s" $$(cat .svnversion))"; \
+		echo "  [SV]  Expanding svnRevisionNo in $1.st"; \
+		sed -e "s/\"\$$SVN\-Revision:\".*\"\$$\"/\"\$$SVN-Revision:\"\'$$rev2\'\"\$$\"/g" $< > .stx_goodies_cypress.svn.st; \
+	fi
+	$(MAKE) CC="$(CLASSLIB_CC)" OPT="$(OPT)" SEPINITCODE="$(SEPINITCODE)" STC="$(STC)" STFILE=.stx_goodies_cypress.svn $(C_RULE);
+	sed -i -e "s/\".stx_goodies_cypress.svn.st\");/\"\stx_goodies_cypress.st\");/g" .stx_goodies_cypress.svn.c
+	$(MAKE) .stx_goodies_cypress.svn.$(O)
+	@mv .stx_goodies_cypress.svn.$(O) stx_goodies_cypress.$(O) 
+endif
+
+
+
+
+# add more install actions here
+install::
+
+# add more install actions for aux-files (resources) here
+installAux::
+
+# add more preMake actions here
+preMake::
+
+# add more postMake actions here
+postMake:: cleanjunk
+
+prereq: $(REQUIRED_SUPPORT_DIRS)
+	cd ../../libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libbasic2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libcomp && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libview && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libdb && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libview2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libboss && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libdb/libodbc && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libdb/libsqlite && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../sunit && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libui && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libbasic3 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libwidg && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libhtml && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libwidg2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libtool && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../libcompat && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../communication && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../monticello && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../librun && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+
+
+
+cleanjunk::
+	-rm -f *.s *.s2
+
+clean::
+	-rm -f *.o *.H
+
+clobber:: clean
+	-rm -f *.so *.dll
+
+
+# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)CypressDefinition.$(O) CypressDefinition.$(H): CypressDefinition.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressDefinitionIndex.$(O) CypressDefinitionIndex.$(H): CypressDefinitionIndex.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressDependencySorter.$(O) CypressDependencySorter.$(H): CypressDependencySorter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressJsonParser.$(O) CypressJsonParser.$(H): CypressJsonParser.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressLoader.$(O) CypressLoader.$(H): CypressLoader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMockBasic.$(O) CypressMockBasic.$(H): CypressMockBasic.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageDefinition.$(O) CypressPackageDefinition.$(H): CypressPackageDefinition.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageReader.$(O) CypressPackageReader.$(H): CypressPackageReader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageWriter.$(O) CypressPackageWriter.$(H): CypressPackageWriter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPatch.$(O) CypressPatch.$(H): CypressPatch.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPatchOperation.$(O) CypressPatchOperation.$(H): CypressPatchOperation.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressSnapshot.$(O) CypressSnapshot.$(H): CypressSnapshot.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressStructure.$(O) CypressStructure.$(H): CypressStructure.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)stx_goodies_cypress.$(O) stx_goodies_cypress.$(H): stx_goodies_cypress.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressAddition.$(O) CypressAddition.$(H): CypressAddition.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressPatchOperation.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressClassDefinition.$(O) CypressClassDefinition.$(H): CypressClassDefinition.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressClassStructure.$(O) CypressClassStructure.$(H): CypressClassStructure.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressStructure.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMethodDefinition.$(O) CypressMethodDefinition.$(H): CypressMethodDefinition.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMethodStructure.$(O) CypressMethodStructure.$(H): CypressMethodStructure.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressStructure.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressModification.$(O) CypressModification.$(H): CypressModification.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressPatchOperation.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageStructure.$(O) CypressPackageStructure.$(H): CypressPackageStructure.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressStructure.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)CypressRemoval.$(O) CypressRemoval.$(H): CypressRemoval.st $(INCLUDE_TOP)/stx/goodies/cypress/CypressPatchOperation.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/ByteArray.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+
+# ENDMAKEDEPEND --- do not remove this line
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Make.spec	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,105 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: stx_goodies_cypress.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# This file contains specifications which are common to all platforms.
+#
+
+# Do NOT CHANGE THESE DEFINITIONS
+# (otherwise, ST/X will have a hard time to find out the packages location from its packageID,
+#  to find the source code of a class and to find the library for a package)
+MODULE=stx
+MODULE_DIR=goodies/cypress
+PACKAGE=$(MODULE):$(MODULE_DIR)
+
+
+# Argument(s) to the stc compiler (stc --usage).
+#  -headerDir=. : create header files locally
+#                (if removed, they will be created as common
+#  -Pxxx       : defines the package
+#  -Zxxx       : a prefix for variables within the classLib
+#  -Dxxx       : defines passed to to CC for inline C-code
+#  -Ixxx       : include path passed to CC for inline C-code
+#  +optspace   : optimized for space
+#  +optspace2  : optimized more for space
+#  +optspace3  : optimized even more for space
+#  +optinline  : generate inline code for some ST constructs
+#  +inlineNew  : additionally inline new
+#  +inlineMath : additionally inline some floatPnt math stuff
+#
+# ********** OPTIONAL: MODIFY the next line(s) ***
+# STCLOCALOPTIMIZATIONS=+optinline +inlineNew
+# STCLOCALOPTIMIZATIONS=+optspace3
+STCLOCALOPTIMIZATIONS=+optspace3
+
+
+# Argument(s) to the stc compiler (stc --usage).
+#  -warn            : no warnings
+#  -warnNonStandard : no warnings about ST/X extensions
+#  -warnEOLComments : no warnings about EOL comment extension
+#  -warnPrivacy     : no warnings about privateClass extension
+#
+# ********** OPTIONAL: MODIFY the next line(s) ***
+# STCWARNINGS=-warn
+# STCWARNINGS=-warnNonStandard
+# STCWARNINGS=-warnEOLComments
+STCWARNINGS=-warnNonStandard
+
+COMMON_CLASSES= \
+	CypressDefinition \
+	CypressDefinitionIndex \
+	CypressDependencySorter \
+	CypressJsonParser \
+	CypressLoader \
+	CypressMockBasic \
+	CypressPackageDefinition \
+	CypressPackageReader \
+	CypressPackageWriter \
+	CypressPatch \
+	CypressPatchOperation \
+	CypressSnapshot \
+	CypressStructure \
+	stx_goodies_cypress \
+	CypressAddition \
+	CypressClassDefinition \
+	CypressClassStructure \
+	CypressMethodDefinition \
+	CypressMethodStructure \
+	CypressModification \
+	CypressPackageStructure \
+	CypressRemoval \
+
+
+
+
+COMMON_OBJS= \
+    $(OUTDIR)CypressDefinition.$(O) \
+    $(OUTDIR)CypressDefinitionIndex.$(O) \
+    $(OUTDIR)CypressDependencySorter.$(O) \
+    $(OUTDIR)CypressJsonParser.$(O) \
+    $(OUTDIR)CypressLoader.$(O) \
+    $(OUTDIR)CypressMockBasic.$(O) \
+    $(OUTDIR)CypressPackageDefinition.$(O) \
+    $(OUTDIR)CypressPackageReader.$(O) \
+    $(OUTDIR)CypressPackageWriter.$(O) \
+    $(OUTDIR)CypressPatch.$(O) \
+    $(OUTDIR)CypressPatchOperation.$(O) \
+    $(OUTDIR)CypressSnapshot.$(O) \
+    $(OUTDIR)CypressStructure.$(O) \
+    $(OUTDIR)stx_goodies_cypress.$(O) \
+    $(OUTDIR)CypressAddition.$(O) \
+    $(OUTDIR)CypressClassDefinition.$(O) \
+    $(OUTDIR)CypressClassStructure.$(O) \
+    $(OUTDIR)CypressMethodDefinition.$(O) \
+    $(OUTDIR)CypressMethodStructure.$(O) \
+    $(OUTDIR)CypressModification.$(O) \
+    $(OUTDIR)CypressPackageStructure.$(O) \
+    $(OUTDIR)CypressRemoval.$(O) \
+    $(OUTDIR)extensions.$(O) \
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Makefile	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,19 @@
+#
+# DO NOT EDIT
+#
+# make uses this file (Makefile) only, if there is no
+# file named "makefile" (lower-case m) in the same directory.
+# My only task is to generate the real makefile and call make again.
+# Thereafter, I am no longer used and needed.
+#
+
+.PHONY: run
+
+run: makefile
+	$(MAKE) -f makefile
+
+#only needed for the definition of $(TOP)
+include Make.proto
+
+makefile:
+	$(TOP)/rules/stmkmf
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/abbrev.stc	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,31 @@
+# automagically generated by the project definition
+# this file is needed for stc to be able to compile modules independently.
+# it provides information about a classes filename, category and especially namespace.
+CypressAbstractTest CypressAbstractTest stx:goodies/cypress 'Cypress-Tests' 1
+CypressDefinition CypressDefinition stx:goodies/cypress 'Cypress-Definitions' 0
+CypressDefinitionIndex CypressDefinitionIndex stx:goodies/cypress 'Cypress-Definitions' 0
+CypressDependencySorter CypressDependencySorter stx:goodies/cypress 'Cypress-Definitions' 0
+CypressJsonParser CypressJsonParser stx:goodies/cypress 'Cypress-Structure' 0
+CypressLoader CypressLoader stx:goodies/cypress 'Cypress-Definitions' 0
+CypressMockBasic CypressMockBasic stx:goodies/cypress 'Cypress-Mocks' 1
+CypressPackageDefinition CypressPackageDefinition stx:goodies/cypress 'Cypress-Definitions' 0
+CypressPackageReader CypressPackageReader stx:goodies/cypress 'Cypress-Structure' 0
+CypressPackageWriter CypressPackageWriter stx:goodies/cypress 'Cypress-Structure' 1
+CypressPatch CypressPatch stx:goodies/cypress 'Cypress-Definitions' 0
+CypressPatchOperation CypressPatchOperation stx:goodies/cypress 'Cypress-Definitions' 0
+CypressSnapshot CypressSnapshot stx:goodies/cypress 'Cypress-Definitions' 0
+CypressStructure CypressStructure stx:goodies/cypress 'Cypress-Structure' 0
+stx_goodies_cypress stx_goodies_cypress stx:goodies/cypress '* Projects & Packages *' 3
+CypressAddition CypressAddition stx:goodies/cypress 'Cypress-Definitions' 0
+CypressClassDefinition CypressClassDefinition stx:goodies/cypress 'Cypress-Definitions' 0
+CypressClassStructure CypressClassStructure stx:goodies/cypress 'Cypress-Structure' 0
+CypressDefinitionTest CypressDefinitionTest stx:goodies/cypress 'Cypress-Tests' 1
+CypressLoaderTest CypressLoaderTest stx:goodies/cypress 'Cypress-Tests' 1
+CypressMethodDefinition CypressMethodDefinition stx:goodies/cypress 'Cypress-Definitions' 0
+CypressMethodStructure CypressMethodStructure stx:goodies/cypress 'Cypress-Structure' 0
+CypressModification CypressModification stx:goodies/cypress 'Cypress-Definitions' 0
+CypressPackageStructure CypressPackageStructure stx:goodies/cypress 'Cypress-Structure' 0
+CypressPatchTest CypressPatchTest stx:goodies/cypress 'Cypress-Tests' 1
+CypressRemoval CypressRemoval stx:goodies/cypress 'Cypress-Definitions' 0
+CypressSnapshotTest CypressSnapshotTest stx:goodies/cypress 'Cypress-Tests' 1
+CypressStructureTest CypressStructureTest stx:goodies/cypress 'Cypress-Tests' 1
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/bc.mak	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,103 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: stx_goodies_cypress.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# Notice, that the name bc.mak is historical (from times, when only borland c was supported).
+# This file contains make rules for the win32 platform using either borland-bcc or visual-c.
+# It shares common definitions with the unix-make in Make.spec.
+# The bc.mak supports the following targets:
+#    bmake         - compile all st-files to a classLib (dll)
+#    bmake clean   - clean all temp files
+#    bmake clobber - clean all
+#
+# Historic Note:
+#  this used to contain only rules to make with borland 
+#    (called via bmake, by "make.exe -f bc.mak")
+#  this has changed; it is now also possible to build using microsoft visual c
+#    (called via vcmake, by "make.exe -f bc.mak -DUSEVC")
+#
+TOP=..\..
+INCLUDE_TOP=$(TOP)\..
+
+
+
+!INCLUDE $(TOP)\rules\stdHeader_bc
+
+!INCLUDE Make.spec
+
+LIBNAME=libstx_goodies_cypress
+RESFILES=cypress.res
+
+
+
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\monticello -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic2 -I$(INCLUDE_TOP)\stx\libcompat -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libcomp -I$(INCLUDE_TOP)\stx\libhtml
+LOCALDEFINES=
+
+STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
+LOCALLIBS=
+
+OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
+
+ALL::  classLibRule
+
+classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
+
+!INCLUDE $(TOP)\rules\stdRules_bc
+
+# build all prerequisite packages for this package
+prereq:
+	pushd ..\..\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libbasic2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libcomp & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libview & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libdb & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libview2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libboss & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libdb\libodbc & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libdb\libsqlite & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\sunit & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libui & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libbasic3 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libwidg & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libhtml & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libwidg2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libtool & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\libcompat & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\communication & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\monticello & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\librun & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+
+
+
+
+
+# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)CypressDefinition.$(O) CypressDefinition.$(H): CypressDefinition.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressDefinitionIndex.$(O) CypressDefinitionIndex.$(H): CypressDefinitionIndex.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressDependencySorter.$(O) CypressDependencySorter.$(H): CypressDependencySorter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressJsonParser.$(O) CypressJsonParser.$(H): CypressJsonParser.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressLoader.$(O) CypressLoader.$(H): CypressLoader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMockBasic.$(O) CypressMockBasic.$(H): CypressMockBasic.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageDefinition.$(O) CypressPackageDefinition.$(H): CypressPackageDefinition.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageReader.$(O) CypressPackageReader.$(H): CypressPackageReader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageWriter.$(O) CypressPackageWriter.$(H): CypressPackageWriter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPatch.$(O) CypressPatch.$(H): CypressPatch.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPatchOperation.$(O) CypressPatchOperation.$(H): CypressPatchOperation.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressSnapshot.$(O) CypressSnapshot.$(H): CypressSnapshot.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressStructure.$(O) CypressStructure.$(H): CypressStructure.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)stx_goodies_cypress.$(O) stx_goodies_cypress.$(H): stx_goodies_cypress.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressAddition.$(O) CypressAddition.$(H): CypressAddition.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressPatchOperation.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressClassDefinition.$(O) CypressClassDefinition.$(H): CypressClassDefinition.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressClassStructure.$(O) CypressClassStructure.$(H): CypressClassStructure.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressStructure.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMethodDefinition.$(O) CypressMethodDefinition.$(H): CypressMethodDefinition.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressMethodStructure.$(O) CypressMethodStructure.$(H): CypressMethodStructure.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressStructure.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressModification.$(O) CypressModification.$(H): CypressModification.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressPatchOperation.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressPackageStructure.$(O) CypressPackageStructure.$(H): CypressPackageStructure.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressStructure.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CypressRemoval.$(O) CypressRemoval.$(H): CypressRemoval.st $(INCLUDE_TOP)\stx\goodies\cypress\CypressPatchOperation.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\ByteArray.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+
+# ENDMAKEDEPEND --- do not remove this line
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/bmake.bat	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,8 @@
+@REM -------
+@REM make using borland bcc
+@REM type bmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+make.exe -N -f bc.mak %*
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cypress.rc	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,37 @@
+//
+// DO NOT EDIT
+// automagically generated from the projectDefinition: stx_goodies_cypress.
+//
+VS_VERSION_INFO VERSIONINFO
+  FILEVERSION     6,2,0,1
+  PRODUCTVERSION  6,2,3,1
+#if (__BORLANDC__)
+  FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
+  FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
+  FILEOS          VOS_NT_WINDOWS32
+  FILETYPE        VFT_DLL
+  FILESUBTYPE     VS_USER_DEFINED
+#endif
+
+BEGIN
+  BLOCK "StringFileInfo"
+  BEGIN
+    BLOCK "040904E4"
+    BEGIN
+      VALUE "CompanyName", "eXept Software AG\0"
+      VALUE "FileDescription", "Smalltalk/X Class library (LIB)\0"
+      VALUE "FileVersion", "6.2.0.1\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", "Thu, 30 Aug 2012 11:46:23 GMT\0"
+    END
+
+  END
+
+  BLOCK "VarFileInfo"
+  BEGIN                               //  Language   |    Translation
+    VALUE "Translation", 0x409, 0x4E4 // U.S. English, Windows Multilingual
+  END
+END
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/extensions.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,34 @@
+"{ Package: 'stx:goodies/cypress' }"!
+
+!CharacterArray methodsFor:'Compatibility-Cuis'!
+
+withLineEndings: lineEndString
+    | stringColl |
+
+    self assert: lineEndString size == 1.
+
+    stringColl := self asStringCollection.
+
+    ^stringColl
+        asStringWith: lineEndString first 
+        from:1 to:(stringColl size) 
+        compressTabs:false 
+        final:nil
+
+    "Created: / 30-08-2012 / 11:27:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CharacterArray class methodsFor:'Compatibility-Cuis'!
+
+lfString
+
+    ^String with: Character lf.
+
+    "Created: / 30-08-2012 / 11:27:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!stx_goodies_cypress class methodsFor:'documentation'!
+
+extensionsVersion_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/lcmake.bat	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,8 @@
+@REM -------
+@REM make using lcc compiler
+@REM type lcmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+make.exe -N -f bc.mak USELCC=1 %1 %2
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/libInit.cc	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,55 @@
+/*
+ * $Header$
+ *
+ * DO NOT EDIT
+ * automagically generated from the projectDefinition: stx_goodies_cypress.
+ */
+#define __INDIRECTVMINITCALLS__
+#include <stc.h>
+
+#ifdef WIN32
+# pragma codeseg INITCODE "INITCODE"
+#endif
+
+#if defined(INIT_TEXT_SECTION) || defined(DLL_EXPORT)
+DLL_EXPORT void _libstx_goodies_cypress_Init() INIT_TEXT_SECTION;
+// DLL_EXPORT void _libstx_goodies_cypress_InitDefinition() INIT_TEXT_SECTION;
+#endif
+
+// void _libstx_goodies_cypress_InitDefinition(pass, __pRT__, snd)
+// OBJ snd; struct __vmData__ *__pRT__; {
+// __BEGIN_PACKAGE2__("libstx_goodies_cypress__DFN", _libstx_goodies_cypress_InitDefinition, "stx:goodies/cypress");
+// _stx_137goodies_137cypress_Init(pass,__pRT__,snd);
+
+// __END_PACKAGE__();
+// }
+
+void _libstx_goodies_cypress_Init(pass, __pRT__, snd)
+OBJ snd; struct __vmData__ *__pRT__; {
+__BEGIN_PACKAGE2__("libstx_goodies_cypress", _libstx_goodies_cypress_Init, "stx:goodies/cypress");
+_CypressDefinition_Init(pass,__pRT__,snd);
+_CypressDefinitionIndex_Init(pass,__pRT__,snd);
+_CypressDependencySorter_Init(pass,__pRT__,snd);
+_CypressJsonParser_Init(pass,__pRT__,snd);
+_CypressLoader_Init(pass,__pRT__,snd);
+_CypressMockBasic_Init(pass,__pRT__,snd);
+_CypressPackageDefinition_Init(pass,__pRT__,snd);
+_CypressPackageReader_Init(pass,__pRT__,snd);
+_CypressPackageWriter_Init(pass,__pRT__,snd);
+_CypressPatch_Init(pass,__pRT__,snd);
+_CypressPatchOperation_Init(pass,__pRT__,snd);
+_CypressSnapshot_Init(pass,__pRT__,snd);
+_CypressStructure_Init(pass,__pRT__,snd);
+_stx_137goodies_137cypress_Init(pass,__pRT__,snd);
+_CypressAddition_Init(pass,__pRT__,snd);
+_CypressClassDefinition_Init(pass,__pRT__,snd);
+_CypressClassStructure_Init(pass,__pRT__,snd);
+_CypressMethodDefinition_Init(pass,__pRT__,snd);
+_CypressMethodStructure_Init(pass,__pRT__,snd);
+_CypressModification_Init(pass,__pRT__,snd);
+_CypressPackageStructure_Init(pass,__pRT__,snd);
+_CypressRemoval_Init(pass,__pRT__,snd);
+
+_stx_137goodies_137cypress_extensions_Init(pass,__pRT__,snd);
+__END_PACKAGE__();
+}
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/stx_goodies_cypress.st	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,154 @@
+"{ Package: 'stx:goodies/cypress' }"
+
+LibraryDefinition subclass:#stx_goodies_cypress
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'* Projects & Packages *'
+!
+
+
+!stx_goodies_cypress class methodsFor:'description'!
+
+excludedFromPreRequisites
+    "list all packages which should be ignored in the automatic
+     preRequisites scan. See #preRequisites for more."
+
+    ^ #(
+    )
+!
+
+preRequisites
+    "list all required packages.
+     This list can be maintained manually or (better) generated and
+     updated by scanning the superclass hierarchies and looking for
+     global variable accesses. (the browser has a menu function for that)
+     Howevery, often too much is found, and you may want to explicitely
+     exclude individual packages in the #excludedFromPrerequisites method."
+
+    ^ #(
+        #'stx:goodies/monticello'
+        #'stx:goodies/sunit'    "TestCase - superclass of CypressStructureTest "
+        #'stx:libbasic'    "ProjectDefinition - superclass of stx_goodies_cypress "
+        #'stx:libbasic2'
+        #'stx:libbasic3'    "ChangeSet - referenced by CypressPackageDefinition>>snapshot "
+        #'stx:libcomp'    "Parser - referenced by CypressPackageReader>>readMethodStructureFor:in:methodProperties: "
+        #'stx:libcompat'
+        #'stx:libhtml'
+    )
+! !
+
+!stx_goodies_cypress class methodsFor:'description - contents'!
+
+classNamesAndAttributes
+    "lists the classes which are to be included in the project.
+     Each entry in the list may be: a single class-name (symbol),
+     or an array-literal consisting of class name and attributes.
+     Attributes are: #autoload or #<os> where os is one of win32, unix,..."
+
+    ^ #(
+        "<className> or (<className> attributes...) in load order"
+        (CypressAbstractTest autoload)
+        CypressDefinition
+        CypressDefinitionIndex
+        CypressDependencySorter
+        CypressJsonParser
+        CypressLoader
+        CypressMockBasic
+        CypressPackageDefinition
+        CypressPackageReader
+        CypressPackageWriter
+        CypressPatch
+        CypressPatchOperation
+        CypressSnapshot
+        CypressStructure
+        #'stx_goodies_cypress'
+        CypressAddition
+        CypressClassDefinition
+        CypressClassStructure
+        (CypressDefinitionTest autoload)
+        (CypressLoaderTest autoload)
+        CypressMethodDefinition
+        CypressMethodStructure
+        CypressModification
+        CypressPackageStructure
+        (CypressPatchTest autoload)
+        CypressRemoval
+        (CypressSnapshotTest autoload)
+        (CypressStructureTest autoload)
+    )
+!
+
+extensionMethodNames
+    "lists the extension methods which are to be included in the project.
+     Entries are 2-element array literals, consisting of class-name and selector."
+
+    ^ #(
+        CharacterArray withLineEndings:
+        'CharacterArray class' lfString
+    )
+! !
+
+!stx_goodies_cypress class methodsFor:'description - project information'!
+
+applicationIconFileName
+    "Return the name (without suffix) of an icon-file (the app's icon); will be included in the rc-resource file"
+
+    ^ nil
+    "/ ^ self applicationName
+!
+
+companyName
+    "Return a companyname which will appear in <lib>.rc"
+
+    ^ 'eXept Software AG'
+!
+
+description
+    "Return a description string which will appear in vc.def / bc.def"
+
+    ^ 'Smalltalk/X Class library'
+!
+
+legalCopyright
+    "Return a copyright string which will appear in <lib>.rc"
+
+    ^ 'Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 1998-2012'
+!
+
+productInstallDirBaseName
+    "Returns a default installDir which will appear in <app>.nsi.
+     This is usually not the one you want to keep"
+
+    ^ (self package asCollectionOfSubstringsSeparatedByAny:':/') last
+!
+
+productName
+    "Return a product name which will appear in <lib>.rc"
+
+    ^ 'Smalltalk/X'
+! !
+
+!stx_goodies_cypress class methodsFor:'description - svn'!
+
+svnRepositoryUrlString
+    "Return a SVN repository URL of myself.
+     (Generated since 2011-04-08)
+     Do not make the string shorter!!!!!! We have to use fixed-length keyword!!!!!!
+    "        
+
+    ^ '$URL::                                                                                                                        $'
+!
+
+svnRevisionNr
+    "Return a SVN revision number of myself.
+     This number is updated after a commit"
+
+    ^ "$SVN-Revision:"'nil             '"$"
+! !
+
+!stx_goodies_cypress class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/vcmake.bat	Thu Aug 30 11:46:39 2012 +0000
@@ -0,0 +1,12 @@
+@REM -------
+@REM make using microsoft visual c
+@REM type vcmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+
+@if not defined VSINSTALLDIR (
+	call "C:\Program Files\Microsoft Visual Studio 10.0"\VC\bin\vcvars32.bat
+)
+make.exe -N -f bc.mak -DUSEVC %*
+
+