| 12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004 | Smalltalk current createPackage: 'Importer-Exporter'!Object subclass: #AbstractExporter	instanceVariableNames: ''	package: 'Importer-Exporter'!!AbstractExporter commentStamp!I am an abstract exporter for Amber source code.## APIUse `#exportPackage:on:` to export a given package on a Stream.!!AbstractExporter methodsFor: 'accessing'!extensionMethodsOfPackage: aPackage	| result |		result := OrderedCollection new.		(self extensionProtocolsOfPackage: aPackage) do: [ :each |		result addAll: each methods ].			^ result!extensionProtocolsOfPackage: aPackage	| extensionName result |		extensionName := '*', aPackage name.	result := OrderedCollection new.		"The classes must be loaded since it is extensions only.	Therefore sorting (dependency resolution) does not matter here.	Not sorting improves the speed by a number of magnitude."		Smalltalk current classes do: [ :each |		{each. each class} do: [ :behavior |			(behavior protocols includes: extensionName) ifTrue: [				result add: (ExportMethodProtocol name: extensionName theClass: behavior) ] ] ].	^result! !!AbstractExporter methodsFor: 'convenience'!chunkEscape: aString	"Replace all occurrences of !! with !!!! and trim at both ends."	^(aString replace: '!!' with: '!!!!') trimBoth!classNameFor: aClass	^aClass isMetaclass		ifTrue: [ aClass instanceClass name, ' class' ]		ifFalse: [			aClass isNil				ifTrue: [ 'nil' ]				ifFalse: [ aClass name ] ]! !!AbstractExporter methodsFor: 'output'!exportPackage: aPackage on: aStream	self subclassResponsibility! !AbstractExporter subclass: #ChunkExporter	instanceVariableNames: ''	package: 'Importer-Exporter'!!ChunkExporter commentStamp!I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.I do not output any compiled code.!!ChunkExporter methodsFor: 'accessing'!extensionCategoriesOfPackage: aPackage	"Issue #143: sort protocol alphabetically"	| name map result |	name := aPackage name.	result := OrderedCollection new.	(Package sortedClasses: Smalltalk current classes) do: [ :each |		{each. each class} do: [ :aClass |			map := Dictionary new.			aClass protocolsDo: [ :category :methods |				category = ('*', name) ifTrue: [ map at: category put: methods ] ].			result addAll: ((map keys sorted: [:a :b | a <= b ]) collect: [ :category |				MethodCategory name: category theClass: aClass methods: (map at: category) ]) ] ].	^result!methodsOfCategory: aCategory	"Issue #143: sort methods alphabetically"	^(aCategory methods) sorted: [ :a :b | a selector <= b selector ]!ownCategoriesOfClass: aClass	"Answer the protocols of aClass that are not package extensions"		"Issue #143: sort protocol alphabetically"	| map |	map := Dictionary new.	aClass protocolsDo: [ :each :methods |		(each match: '^\*') ifFalse: [ map at: each put: methods ] ].	^(map keys sorted: [:a :b | a <= b ]) collect: [ :each |		MethodCategory name: each theClass: aClass methods: (map at: each) ]!ownCategoriesOfMetaClass: aClass	"Issue #143: sort protocol alphabetically"	^self ownCategoriesOfClass: aClass class!ownMethodProtocolsOfClass: aClass	"Answer a collection of ExportMethodProtocol object of aClass that are not package extensions"		^ aClass ownProtocols collect: [ :each |		ExportMethodProtocol name: each theClass: aClass ]! !!ChunkExporter methodsFor: 'fileOut'!recipe	"Export a given package."	| exportCategoryRecipe |	exportCategoryRecipe := {		self -> #exportCategoryPrologueOf:on:.		{			self -> #methodsOfCategory:.			self -> #exportMethod:on: }.		self -> #exportCategoryEpilogueOf:on: }.	^{		self -> #exportPackageDefinitionOf:on:.		{			PluggableExporter -> #ownClassesOfPackage:.			self -> #exportDefinitionOf:on:.			{ self -> #ownCategoriesOfClass: }, exportCategoryRecipe.			self -> #exportMetaDefinitionOf:on:.			{ self -> #ownCategoriesOfMetaClass: }, exportCategoryRecipe }.		{ self -> #extensionCategoriesOfPackage: }, exportCategoryRecipe	}! !!ChunkExporter methodsFor: 'output'!exportCategoryEpilogueOf: aCategory on: aStream	aStream nextPutAll: ' !!'; lf; lf!exportCategoryPrologueOf: aCategory on: aStream	aStream		nextPutAll: '!!', (self classNameFor: aCategory theClass);		nextPutAll: ' methodsFor: ''', aCategory name, '''!!'!exportDefinitionOf: aClass on: aStream	"Chunk format."	aStream		nextPutAll: (self classNameFor: aClass superclass);		nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;		tab; nextPutAll: 'instanceVariableNames: '''.	aClass instanceVariableNames		do: [:each | aStream nextPutAll: each]		separatedBy: [aStream nextPutAll: ' '].	aStream		nextPutAll: ''''; lf;		tab; nextPutAll: 'package: ''', aClass category, '''!!'; lf.	aClass comment notEmpty ifTrue: [		aStream		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;		nextPutAll: (self chunkEscape: aClass comment), '!!';lf].	aStream lf!exportMetaDefinitionOf: aClass on: aStream	aClass class instanceVariableNames isEmpty ifFalse: [		aStream			nextPutAll: (self classNameFor: aClass class);			nextPutAll: ' instanceVariableNames: '''.		aClass class instanceVariableNames			do: [:each | aStream nextPutAll: each]			separatedBy: [aStream nextPutAll: ' '].		aStream			nextPutAll: '''!!'; lf; lf]!exportMethod: aMethod on: aStream	aStream		lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;		nextPutAll: '!!'!exportPackage: aPackage on: aStream	self exportPackageDefinitionOf: aPackage on: aStream.		aPackage sortedClasses do: [ :each |		self exportDefinitionOf: each on: aStream.				self 			exportProtocols: (self ownMethodProtocolsOfClass: each)			on: aStream.					self exportMetaDefinitionOf: each on: aStream.				self 			exportProtocols: (self ownMethodProtocolsOfClass: each class)			on: aStream ].				self 		exportProtocols: (self extensionProtocolsOfPackage: aPackage)		on: aStream!exportPackageDefinitionOf: aPackage on: aStream	aStream		nextPutAll: 'Smalltalk current createPackage: ''', aPackage name, '''!!';		lf!exportProtocol: aProtocol on: aStream	self exportProtocolPrologueOf: aProtocol on: aStream.	aProtocol methods do: [ :method | 		self exportMethod: method on: aStream ].	self exportProtocolEpilogueOf: aProtocol on: aStream!exportProtocolEpilogueOf: aProtocol on: aStream	aStream nextPutAll: ' !!'; lf; lf!exportProtocolPrologueOf: aProtocol on: aStream	aStream		nextPutAll: '!!', (self classNameFor: aProtocol theClass);		nextPutAll: ' methodsFor: ''', aProtocol name, '''!!'!exportProtocols: aCollection on: aStream	aCollection do: [ :each |		self exportProtocol: each on: aStream ]! !AbstractExporter subclass: #Exporter	instanceVariableNames: ''	package: 'Importer-Exporter'!!Exporter commentStamp!I am responsible for outputting Amber code into a JavaScript string.The generated output is enough to reconstruct the exported data, including Smalltalk source code and other metadata.## Use caseI am typically used to save code outside of the Amber runtime (committing to disk, etc.).!!Exporter methodsFor: 'accessing'!ownMethodsOfClass: aClass	"Issue #143: sort methods alphabetically"	^((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector])		reject: [:each | (each category match: '^\*')]!ownMethodsOfMetaClass: aClass	"Issue #143: sort methods alphabetically"	^self ownMethodsOfClass: aClass class! !!Exporter methodsFor: 'convenience'!classNameFor: aClass	^aClass isMetaclass		ifTrue: [ aClass instanceClass name, '.klass' ]		ifFalse: [			aClass isNil				ifTrue: [ 'nil' ]				ifFalse: [ aClass name ] ]! !!Exporter methodsFor: 'fileOut'!amdRecipe	"Export a given package with amd transport type."	| result |	result := self recipe.	result first key: AmdExporter.	result last key: AmdExporter.	^result!recipe	"Export a given package."	^{		self -> #exportPackagePrologueOf:on:.		self -> #exportPackageDefinitionOf:on:.		self -> #exportPackageTransportOf:on:.		{			PluggableExporter -> #ownClassesOfPackage:.			self -> #exportDefinitionOf:on:.			{				self -> #ownMethodsOfClass:.				self -> #exportMethod:on: }.			self -> #exportMetaDefinitionOf:on:.			{				self -> #ownMethodsOfMetaClass:.				self -> #exportMethod:on: } }.		{			self -> #extensionMethodsOfPackage:.			self -> #exportMethod:on: }.		self -> #exportPackageEpilogueOf:on:	}! !!Exporter methodsFor: 'output'!exportDefinitionOf: aClass on: aStream	aStream		lf;		nextPutAll: 'smalltalk.addClass(';		nextPutAll: '''', (self classNameFor: aClass), ''', ';		nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);		nextPutAll: ', ['.	aClass instanceVariableNames		do: [:each | aStream nextPutAll: '''', each, '''']		separatedBy: [aStream nextPutAll: ', '].	aStream		nextPutAll: '], ''';		nextPutAll: aClass category, '''';		nextPutAll: ');'.	aClass comment notEmpty ifTrue: [		aStream			lf;		nextPutAll: 'smalltalk.';		nextPutAll: (self classNameFor: aClass);		nextPutAll: '.comment=';		nextPutAll: aClass comment asJavascript;		nextPutAll: ';'].	aStream lf!exportMetaDefinitionOf: aClass on: aStream	aStream lf.	aClass class instanceVariableNames isEmpty ifFalse: [		aStream		nextPutAll: 'smalltalk.', (self classNameFor: aClass class);		nextPutAll: '.iVarNames = ['.		aClass class instanceVariableNames		do: [:each | aStream nextPutAll: '''', each, '''']		separatedBy: [aStream nextPutAll: ','].		aStream nextPutAll: '];', String lf]!exportMethod: aMethod on: aStream	aStream		nextPutAll: 'smalltalk.addMethod(';lf;		"nextPutAll: aMethod selector asSelector asJavascript, ',';lf;"		nextPutAll: 'smalltalk.method({';lf;		nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;		nextPutAll: 'category: ''', aMethod category, ''',';lf;		nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;		nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;		nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;		nextPutAll: 'messageSends: ', aMethod messageSends asJavascript, ',';lf;		nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript.	aStream		lf;		nextPutAll: '}),';lf;		nextPutAll: 'smalltalk.', (self classNameFor: aMethod methodClass);		nextPutAll: ');';lf;lf!exportPackage: aPackage on: aStream		self 		exportPackagePrologueOf: aPackage on: aStream;		exportPackageDefinitionOf: aPackage on: aStream;		exportPackageTransportOf: aPackage on: aStream.		aPackage sortedClasses do: [ :each |		self exportDefinitionOf: each on: aStream.		each ownMethods do: [ :method |			self exportMethod: method on: aStream ].					self exportMetaDefinitionOf: each on: aStream.		each class ownMethods do: [ :method |			self exportMethod: method on: aStream ] ].				(self extensionMethodsOfPackage: aPackage) do: [ :each |		self exportMethod: each on: aStream ].			self exportPackageEpilogueOf: aPackage on: aStream!exportPackageDefinitionOf: aPackage on: aStream	aStream		nextPutAll: 'smalltalk.addPackage(';		nextPutAll: '''', aPackage name, ''');';		lf!exportPackageEpilogueOf: aPackage on: aStream	aStream		nextPutAll: '})(global_smalltalk,global_nil,global__st);';		lf!exportPackagePrologueOf: aPackage on: aStream	aStream		nextPutAll: '(function(smalltalk,nil,_st){';		lf!exportPackageTransportOf: aPackage on: aStream	| json |	json := aPackage transportJson.	json = 'null' ifFalse: [		aStream			nextPutAll: 'smalltalk.packages[';			nextPutAll: aPackage name asJavascript;			nextPutAll: '].transport = ';			nextPutAll: json;			nextPutAll: ';';			lf ]! !Exporter subclass: #AmdExporter	instanceVariableNames: 'namespace'	package: 'Importer-Exporter'!!AmdExporter commentStamp!I am used to export Packages in an AMD (Asynchronous Module Definition) JavaScript format.!!AmdExporter methodsFor: 'output'!exportPackageEpilogueOf: aPackage on: aStream	aStream		nextPutAll: '});';		lf!exportPackagePrologueOf: aPackage on: aStream	aStream		nextPutAll: 'define("';		nextPutAll: (self amdNamespaceOfPackage: aPackage);		nextPutAll: '/';		nextPutAll: aPackage name;		nextPutAll: '", ';		nextPutAll: (#('amber_vm/smalltalk' 'amber_vm/nil' 'amber_vm/_st'), (self amdNamesOfPackages: aPackage loadDependencies)) asJavascript;		nextPutAll: ', function(smalltalk,nil,_st){';		lf! !!AmdExporter methodsFor: 'private'!amdNamesOfPackages: anArray	^ (anArray		select: [ :each | (self amdNamespaceOfPackage: each) notNil ])		collect: [ :each | (self amdNamespaceOfPackage: each), '/', each name ]!amdNamespaceOfPackage: aPackage	^ (aPackage transport type = 'amd')		ifTrue: [ aPackage transport namespace ]		ifFalse: [ nil ]! !Object subclass: #ChunkParser	instanceVariableNames: 'stream'	package: 'Importer-Exporter'!!ChunkParser commentStamp!I am responsible for parsing aStream contents in the chunk format.## API    ChunkParser new        stream: aStream;        nextChunk!!ChunkParser methodsFor: 'accessing'!stream: aStream	stream := aStream! !!ChunkParser methodsFor: 'reading'!nextChunk	"The chunk format (Smalltalk Interchange Format or Fileout format)	is a trivial format but can be a bit tricky to understand:		- Uses the exclamation mark as delimiter of chunks.		- Inside a chunk a normal exclamation mark must be doubled.		- A non empty chunk must be a valid Smalltalk expression.		- A chunk on top level with a preceding empty chunk is an instruction chunk:			- The object created by the expression then takes over reading chunks.	This method returns next chunk as a String (trimmed), empty String (all whitespace) or nil."	| char result chunk |	result := '' writeStream.		[char := stream next.		char notNil] whileTrue: [				char = '!!' ifTrue: [						stream peek = '!!'								ifTrue: [stream next "skipping the escape double"]								ifFalse: [^result contents trimBoth "chunk end marker found"]].				result nextPut: char].	^nil "a chunk needs to end with !!"! !!ChunkParser class methodsFor: 'instance creation'!on: aStream	^self new stream: aStream! !Object subclass: #ExportMethodProtocol	instanceVariableNames: 'name theClass'	package: 'Importer-Exporter'!!ExportMethodProtocol commentStamp!I am an abstraction for a method protocol in a class / metaclass.I know of my class, name and methods.I am used when exporting a package.!!ExportMethodProtocol methodsFor: 'accessing'!methods	^ self theClass methodsInProtocol: self name!name	^name!name: aString	name := aString!sortedMethods	^ self methods sorted: [ :a :b | a selector <= b selector ]!theClass	^theClass!theClass: aClass	theClass := aClass! !!ExportMethodProtocol class methodsFor: 'instance creation'!name: aString theClass: aClass	^self new		name: aString;		theClass: aClass;		yourself! !Object subclass: #Importer	instanceVariableNames: ''	package: 'Importer-Exporter'!!Importer commentStamp!I can import Amber code from a string in the chunk format.## API    Importer new import: aString!!Importer methodsFor: 'fileIn'!import: aStream	| chunk result parser lastEmpty |	parser := ChunkParser on: aStream.	lastEmpty := false.	[chunk := parser nextChunk.	chunk isNil] whileFalse: [		chunk isEmpty			ifTrue: [lastEmpty := true]			ifFalse: [				result := Compiler new evaluateExpression: chunk.				lastEmpty						ifTrue: [									lastEmpty := false.									result scanFrom: parser]]]! !Object subclass: #MethodCategory	instanceVariableNames: 'methods name theClass'	package: 'Importer-Exporter'!!MethodCategory commentStamp!I am an abstraction for a method category in a class / metaclass.I know of my class, name and methods.I am used when exporting a package.!!MethodCategory methodsFor: 'accessing'!methods	^methods!methods: aCollection	methods := aCollection!name	^name!name: aString	name := aString!theClass	^theClass!theClass: aClass	theClass := aClass! !!MethodCategory class methodsFor: 'not yet classified'!name: aString theClass: aClass methods: anArray	^self new		name: aString;		theClass: aClass;		methods: anArray;		yourself! !InterfacingObject subclass: #PackageHandler	instanceVariableNames: ''	package: 'Importer-Exporter'!!PackageHandler commentStamp!I am responsible for handling package loading and committing.I should not be used directly. Instead, use the corresponding `Package` methods.!!PackageHandler methodsFor: 'accessing'!chunkContentsFor: aPackage	^ String streamContents: [ :str |		self chunkExporter exportPackage: aPackage on: str ]!chunkExporterClass	^ ChunkExporter!commitPathJsFor: aPackage	self subclassResponsibility!commitPathStFor: aPackage	self subclassResponsibility!contentsFor: aPackage	^ String streamContents: [ :str |		self exporter exportPackage: aPackage on: str ]!exporterClass	^ Exporter! !!PackageHandler methodsFor: 'committing'!commit: aPackage	{		[ self commitStFileFor: aPackage ].		[ self commitJsFileFor: aPackage ]	}		do: [ :each | each value ]		displayingProgress: 'Committing package ', aPackage name!commitJsFileFor: aPackage	self 		ajaxPutAt: (self commitPathJsFor: aPackage), '/', aPackage name, '.js'		data: (self contentsFor: aPackage)!commitStFileFor: aPackage	self 		ajaxPutAt: (self commitPathStFor: aPackage), '/', aPackage name, '.st'		data: (self chunkContentsFor: aPackage)!oldCommit: aPackage		self commitChannels		do: [ :commitStrategyFactory || fileContents commitStrategy |			commitStrategy := commitStrategyFactory value: aPackage.			fileContents := String streamContents: [ :stream |				(PluggableExporter forRecipe: commitStrategy key) exportPackage: aPackage on: stream ].			self ajaxPutAt: commitStrategy value data: fileContents ]		displayingProgress: 'Committing package ', aPackage name! !!PackageHandler methodsFor: 'factory'!chunkExporter	^ self chunkExporterClass new!exporter	^ self exporterClass new! !!PackageHandler methodsFor: 'private'!ajaxPutAt: aURL data: aString	self		ajax: #{			'url' -> aURL.			'type' -> 'PUT'.			'data' -> aString.			'contentType' -> 'text/plain;charset=UTF-8'.			'error' -> [ :xhr | self error: 'Commiting ' , aURL , ' failed with reason: "' , (xhr responseText) , '"'] }! !PackageHandler subclass: #AmdPackageHandler	instanceVariableNames: ''	package: 'Importer-Exporter'!!AmdPackageHandler commentStamp!I am responsible for handling package loading and committing.I should not be used directly. Instead, use the corresponding `Package` methods.!!AmdPackageHandler methodsFor: 'accessing'!commitPathJsFor: aPackage	^self toUrl: (self namespaceFor: aPackage)!commitPathStFor: aPackage	"if _source is not mapped, .st commit will likely fail"	^self toUrl: (self namespaceFor: aPackage), '/_source'.!exporterClass	^ AmdExporter! !!AmdPackageHandler methodsFor: 'committing'!namespaceFor: aPackage	^ aPackage transport namespace! !!AmdPackageHandler methodsFor: 'private'!toUrl: aString	^ Smalltalk current amdRequire		ifNil: [ self error: 'AMD loader not present' ]		ifNotNil: [ :require | (require basicAt: 'toUrl') value: aString ]! !!AmdPackageHandler class methodsFor: 'commit paths'!defaultNamespace	^ Smalltalk current defaultAmdNamespace!defaultNamespace: aString	Smalltalk current defaultAMDNamespace: aString!resetCommitPaths	defaultNamespace := nil! !!AmdPackageHandler class methodsFor: 'initialization'!initialize	super initialize.	self registerFor: AMDPackageTransport type! !Object subclass: #PackageTransport	instanceVariableNames: 'package'	package: 'Importer-Exporter'!!PackageTransport commentStamp!I represent the transport mechanism used to commit a package.My concrete subclasses have a `#handler` to which committing is delegated.!!PackageTransport methodsFor: 'accessing'!commitHandlerClass	self subclassResponsibility!package	^ package!package: aPackage	package := aPackage!type	^ self class type! !!PackageTransport methodsFor: 'committing'!commit	self commitHandler commit: self package! !!PackageTransport methodsFor: 'factory'!commitHandler	^ self commitHandlerClass new! !!PackageTransport methodsFor: 'initialization'!setupFromJson: anObject	"no op. override if needed in subclasses"! !PackageTransport class instanceVariableNames: 'registry'!!PackageTransport class methodsFor: 'accessing'!classRegisteredFor: aString	^ registry at: aString!for: aString	^ (self classRegisteredFor: aString) new!type	"Override in subclasses"	^ nil! !!PackageTransport class methodsFor: 'initialization'!initialize	super initialize.	registry := #{}.	self register! !!PackageTransport class methodsFor: 'registration'!register	PackageTransport register: self!register: aClass	aClass type ifNotNil: [		registry at: aClass type put: aClass ]! !PackageTransport subclass: #AmdPackageTransport	instanceVariableNames: 'namespace'	package: 'Importer-Exporter'!!AmdPackageTransport commentStamp!I am the default transport for committing packages.See `AmdExporter` and `AmdPackageHandler`.!!AmdPackageTransport methodsFor: 'accessing'!commitHandlerClass	^ AmdPackageHandler!namespace	^ namespace ifNil: [ self defaultNamespace ]!namespace: aString	namespace := aString! !!AmdPackageTransport methodsFor: 'defaults'!defaultNamespace	^ Smalltalk current defaultAmdNamespace! !!AmdPackageTransport methodsFor: 'initialization'!setupFromJson: anObject	self namespace: (anObject at: 'amdNamespace')! !!AmdPackageTransport class methodsFor: 'accessing'!type	^ 'amd'! !!AmdPackageTransport class methodsFor: 'instance creation'!namespace: aString	^ self new		namespace: aString;		yourself! !Object subclass: #PluggableExporter	instanceVariableNames: 'recipe'	package: 'Importer-Exporter'!!PluggableExporter commentStamp!I am an engine for exporting structured data on a Stream.My instances are created using  PluggableExporter forRecipe: aRecipe,where recipe is structured description of the exporting algorithm (see `ExportRecipeInterpreter`).The actual exporting is done by interpreting the recipe using a `RecipeInterpreter`.I am used to export amber packages, so I have a convenience method`exportPackage: aPackage on: aStream`which exports `aPackage` using the `recipe`(it is otherwise no special, so it may be renamed to export:on:)!!PluggableExporter methodsFor: 'accessing'!interpreter	^ ExportRecipeInterpreter new!recipe	^recipe!recipe: anArray	recipe := anArray! !!PluggableExporter methodsFor: 'fileOut'!exportAllPackages	"Export all packages in the system."	^String streamContents: [:stream |		Smalltalk current packages do: [:pkg |		self exportPackage: pkg on: stream]]!exportPackage: aPackage on: aStream	self interpreter interpret: self recipe for: aPackage on: aStream! !!PluggableExporter class methodsFor: 'convenience'!ownClassesOfPackage: package	"Export classes in dependency order.	Update (issue #171): Remove duplicates for export"	^package sortedClasses asSet! !!PluggableExporter class methodsFor: 'instance creation'!forRecipe: aRecipe	^self new recipe: aRecipe; yourself! !!Package methodsFor: '*Importer-Exporter'!commit	^ self transport commit!transportJson	<return JSON.stringify(self.transport || null);>!transportType	<return (self.transport && self.transport.type) || 'unknown';>!transport	^ (PackageTransport for: self transportType)		setupFromJson: self basicTransport;		package: self;		yourself!basicTransport	<return self.transport>! !
 |