MCStWriter.st
changeset 42 df170417877c
child 143 d7354b2599b6
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MCStWriter.st	Wed Nov 22 14:06:38 2006 +0100
@@ -0,0 +1,124 @@
+"{ Package: 'stx:goodies/monticello' }"
+
+MCWriter subclass:#MCStWriter
+	instanceVariableNames:'initStream'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Monticello-Chunk Format'
+!
+
+
+!MCStWriter class methodsFor:'as yet unclassified'!
+
+readerClass
+	^ MCStReader
+! !
+
+!MCStWriter methodsFor:'visiting'!
+
+visitClassDefinition: definition
+	self writeClassDefinition: definition.
+	definition hasClassInstanceVariables ifTrue: [self writeMetaclassDefinition: definition].
+	definition hasComment ifTrue: [self writeClassComment: definition].
+!
+
+visitMethodDefinition: definition
+	self writeMethodPreamble: definition.
+	self writeMethodSource: definition.
+	self writeMethodPostscript.
+	self writeMethodInitializer: definition.
+!
+
+visitOrganizationDefinition: defintion
+	defintion categories do: [:cat | self writeCategory: cat].
+! !
+
+!MCStWriter methodsFor:'writing'!
+
+chunkContents: aBlock
+	stream cr; nextChunkPut: (String streamContents: aBlock); cr
+!
+
+writeCategory: categoryName
+	stream
+		nextChunkPut: 'SystemOrganization addCategory: ', categoryName printString;
+		cr
+!
+
+writeClassComment: definition
+	stream
+		cr;
+		nextPut: $!!;
+		nextPutAll: definition className;
+		nextPutAll: ' commentStamp: ';
+		store: definition commentStamp;
+		nextPutAll: ' prior: 0!!';
+		cr;
+		nextChunkPut: definition comment;
+		cr.
+!
+
+writeClassDefinition: definition
+	self chunkContents: [:s | definition printDefinitionOn: stream]
+!
+
+writeDefinitions: aCollection
+	"initStream is an ugly hack until we have proper init defs"
+	initStream := String new writeStream.
+
+	(MCDependencySorter sortItems: aCollection)
+		do: [:ea | ea accept: self]
+		displayingProgress: 'Writing definitions...'.
+	
+	stream nextPutAll: initStream contents.
+!
+
+writeMetaclassDefinition: definition
+	self chunkContents: [:s | s
+		nextPutAll: definition className;
+		nextPutAll: ' class';
+		cr; tab;
+		nextPutAll: 'instanceVariableNames: ''';
+		nextPutAll: definition classInstanceVariablesString;
+		nextPut: $'.
+	]
+!
+
+writeMethodInitializer: aMethodDefinition
+	aMethodDefinition isInitializer ifTrue:
+		[initStream nextChunkPut: aMethodDefinition className, ' initialize'; cr]
+!
+
+writeMethodPostscript
+	stream
+		space;
+		nextPut: $!!;
+		cr
+!
+
+writeMethodPreamble: definition
+	stream
+		cr;
+		nextPut: $!!;
+		nextPutAll: definition fullClassName;
+		nextPutAll: ' methodsFor: ';
+		nextPutAll: definition category asString printString;
+		nextPutAll: ' stamp: ';
+		nextPutAll: definition timeStamp asString printString;
+		nextPutAll: '!!';
+		cr
+!
+
+writeMethodSource: definition
+	stream nextChunkPut: definition source
+!
+
+writeSnapshot: aSnapshot
+	self writeDefinitions: aSnapshot definitions
+! !
+
+!MCStWriter class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStWriter.st,v 1.1 2006-11-22 13:06:38 cg Exp $'
+! !