12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118 |
- Smalltalk createPackage: 'Platform-ImportExport'!
- Object subclass: #AbstractExporter
- instanceVariableNames: ''
- package: 'Platform-ImportExport'!
- !AbstractExporter commentStamp!
- I am an abstract exporter for Amber source code.
- ## API
- Use `#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 topological sorting (dependency resolution) does not matter here.
- Not sorting topologically improves the speed by a number of magnitude.
-
- Not to shuffle diffs, classes are sorted by their name."
-
- (Smalltalk classes asArray sorted: [ :a :b | a name < b name ]) do: [ :each |
- {each. each class} do: [ :behavior |
- (behavior protocols includes: extensionName) ifTrue: [
- result add: (ExportMethodProtocol name: extensionName theClass: behavior) ] ] ].
- ^ result
- ! !
- !AbstractExporter methodsFor: 'convenience'!
- 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: 'Platform-ImportExport'!
- !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 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
- !
- 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: 'convenience'!
- chunkEscape: aString
- "Replace all occurrences of !! with !!!! and trim at both ends."
- ^ (aString replace: '!!' with: '!!!!') trimBoth
- ! !
- !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;
- exportPackageImportsOf: 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 createPackage: ''', aPackage name, '''!!';
- lf
- !
- exportPackageImportsOf: aPackage on: aStream
- aPackage imports ifNotEmpty: [ :imports |
- aStream
- nextPutAll: '(Smalltalk packageAt: ''';
- nextPutAll: aPackage name;
- nextPutAll: ''') imports: ';
- nextPutAll: (self chunkEscape: aPackage importsDefinition);
- nextPutAll: '!!';
- 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: 'Platform-ImportExport'!
- !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 case
- I 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 protocol match: '^\*') ]
- !
- ownMethodsOfMetaClass: aClass
- "Issue #143: sort methods alphabetically"
- ^ self ownMethodsOfClass: aClass class
- ! !
- !Exporter methodsFor: 'convenience'!
- jsClassNameFor: aClass
- ^ aClass isMetaclass
- ifTrue: [ (self jsClassNameFor: aClass instanceClass), '.klass' ]
- ifFalse: [
- aClass
- ifNil: [ 'null' ]
- ifNotNil: [ '$globals.', aClass name ] ]
- ! !
- !Exporter methodsFor: 'output'!
- exportDefinitionOf: aClass on: aStream
- aStream
- lf;
- nextPutAll: '$core.addClass(';
- nextPutAll: '''', (self classNameFor: aClass), ''', ';
- nextPutAll: (self jsClassNameFor: 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: '//>>excludeStart("ide", pragmas.excludeIdeData);';
- lf;
- nextPutAll: (self jsClassNameFor: aClass);
- nextPutAll: '.comment=';
- nextPutAll: aClass comment crlfSanitized asJavascript;
- nextPutAll: ';';
- lf;
- nextPutAll: '//>>excludeEnd("ide");' ].
- aStream lf
- !
- exportMetaDefinitionOf: aClass on: aStream
- aStream lf.
- aClass class instanceVariableNames isEmpty ifFalse: [
- aStream
- nextPutAll: (self jsClassNameFor: 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: '$core.addMethod(';lf;
- nextPutAll: '$core.method({';lf;
- nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
- nextPutAll: 'protocol: ''', aMethod protocol, ''',';lf;
- nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
- nextPutAll: '//>>excludeStart("ide", pragmas.excludeIdeData);';lf;
- nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;
- nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;
- nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript, ',';lf;
- nextPutAll: '//>>excludeEnd("ide");';lf;
- nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;lf;
- nextPutAll: '}),';lf;
- nextPutAll: (self jsClassNameFor: aMethod methodClass);
- nextPutAll: ');';lf;lf
- !
- exportPackage: aPackage on: aStream
-
- self
- exportPackagePrologueOf: aPackage on: aStream;
- exportPackageDefinitionOf: aPackage on: aStream;
- exportPackageContextOf: aPackage on: aStream;
- exportPackageImportsOf: 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
- !
- exportPackageContextOf: aPackage on: aStream
- aStream
- nextPutAll: '$core.packages[';
- nextPutAll: aPackage name asJavascript;
- nextPutAll: '].innerEval = ';
- nextPutAll: 'function (expr) { return eval(expr); }';
- nextPutAll: ';';
- lf
- !
- exportPackageDefinitionOf: aPackage on: aStream
- aStream
- nextPutAll: '$core.addPackage(';
- nextPutAll: '''', aPackage name, ''');';
- lf
- !
- exportPackageEpilogueOf: aPackage on: aStream
- self subclassResponsibility
- !
- exportPackageImportsOf: aPackage on: aStream
- aPackage importsAsJson ifNotEmpty: [ :imports |
- aStream
- nextPutAll: '$core.packages[';
- nextPutAll: aPackage name asJavascript;
- nextPutAll: '].imports = ';
- nextPutAll: imports asJavascript;
- nextPutAll: ';';
- lf ]
- !
- exportPackagePrologueOf: aPackage on: aStream
- self subclassResponsibility
- !
- exportPackageTransportOf: aPackage on: aStream
- aStream
- nextPutAll: '$core.packages[';
- nextPutAll: aPackage name asJavascript;
- nextPutAll: '].transport = ';
- nextPutAll: aPackage transport asJSONString;
- nextPutAll: ';';
- lf
- ! !
- Exporter subclass: #AmdExporter
- instanceVariableNames: 'namespace'
- package: 'Platform-ImportExport'!
- !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
- | importsForOutput loadDependencies pragmaStart pragmaEnd |
- pragmaStart := ''.
- pragmaEnd := ''.
- importsForOutput := self importsForOutput: aPackage.
- loadDependencies := self amdNamesOfPackages: aPackage loadDependencies.
- importsForOutput value ifNotEmpty: [
- pragmaStart := String lf, '//>>excludeStart("imports", pragmas.excludeImports);', String lf.
- pragmaEnd := String lf, '//>>excludeEnd("imports");', String lf ].
- aStream
- nextPutAll: 'define("';
- nextPutAll: (self amdNamespaceOfPackage: aPackage);
- nextPutAll: '/';
- nextPutAll: aPackage name;
- nextPutAll: '", ';
- nextPutAll: (((
- (#('amber/boot' ':1:'), importsForOutput value, #(':2:'), loadDependencies) asJavascript)
- replace: ',\s*["'']:1:["'']' with: pragmaStart) replace: ',\s*["'']:2:["'']' with: pragmaEnd);
- nextPutAll: ', function(';
- nextPutAll: (((
- (#('$boot' ':1:'), importsForOutput key, #(':2:')) join: ',')
- replace: ',\s*:1:' with: pragmaStart) replace: ',\s*:2:' with: pragmaEnd);
- nextPutAll: '){';
- lf;
- nextPutAll: 'var $core=$boot.api,nil=$boot.nil,$recv=$boot.asReceiver,$globals=$boot.globals;';
- 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 ]
- !
- importsForOutput: aPackage
- "Returns an association where key is list of import variables
- and value is list of external dependencies, with ones imported as variables
- put at the beginning with same order as is in key.
-
- For example imports:{'jQuery'->'jquery'. 'bootstrap'} would yield
- #('jQuery') -> #('jquery' 'bootstrap')"
- | namedImports anonImports importVarNames |
- namedImports := #().
- anonImports := #().
- importVarNames := #().
- aPackage imports do: [ :each | each isString
- ifTrue: [ anonImports add: each ]
- ifFalse: [ namedImports add: each value.
- importVarNames add: each key ]].
- ^ importVarNames -> (namedImports, anonImports)
- ! !
- Object subclass: #ChunkParser
- instanceVariableNames: 'stream last'
- package: 'Platform-ImportExport'!
- !ChunkParser commentStamp!
- I am responsible for parsing aStream contents in the chunk format.
- ## API
- ChunkParser new
- stream: aStream;
- nextChunk!
- !ChunkParser methodsFor: 'accessing'!
- last
- ^ last
- !
- 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: [ ^ last := result contents trimBoth "chunk end marker found" ]].
- result nextPut: char ].
- ^ last := nil "a chunk needs to end with !!"
- ! !
- !ChunkParser class methodsFor: 'instance creation'!
- on: aStream
- ^ self new stream: aStream
- ! !
- Object subclass: #ClassCommentReader
- instanceVariableNames: 'class'
- package: 'Platform-ImportExport'!
- !ClassCommentReader commentStamp!
- I provide a mechanism for retrieving class comments stored on a file.
- See also `ClassCategoryReader`.!
- !ClassCommentReader methodsFor: 'accessing'!
- class: aClass
- class := aClass
- ! !
- !ClassCommentReader methodsFor: 'fileIn'!
- scanFrom: aChunkParser
- | chunk |
- chunk := aChunkParser nextChunk.
- chunk isEmpty ifFalse: [
- self setComment: chunk ].
- ! !
- !ClassCommentReader methodsFor: 'initialization'!
- initialize
- super initialize.
- ! !
- !ClassCommentReader methodsFor: 'private'!
- setComment: aString
- class comment: aString
- ! !
- Object subclass: #ClassProtocolReader
- instanceVariableNames: 'class category'
- package: 'Platform-ImportExport'!
- !ClassProtocolReader commentStamp!
- I provide a mechanism for retrieving class descriptions stored on a file in the Smalltalk chunk format.!
- !ClassProtocolReader methodsFor: 'accessing'!
- class: aClass category: aString
- class := aClass.
- category := aString
- ! !
- !ClassProtocolReader methodsFor: 'fileIn'!
- scanFrom: aChunkParser
- | chunk |
- [ chunk := aChunkParser nextChunk.
- chunk isEmpty ] whileFalse: [
- self compileMethod: chunk ].
- ClassBuilder new setupClass: class
- ! !
- !ClassProtocolReader methodsFor: 'initialization'!
- initialize
- super initialize.
- ! !
- !ClassProtocolReader methodsFor: 'private'!
- compileMethod: aString
- Compiler new install: aString forClass: class protocol: category
- ! !
- Object subclass: #ExportMethodProtocol
- instanceVariableNames: 'name theClass'
- package: 'Platform-ImportExport'!
- !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)
- sorted: [ :a :b | a selector <= b selector ]
- !
- name
- ^ name
- !
- name: aString
- name := aString
- !
- 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: 'lastSection lastChunk'
- package: 'Platform-ImportExport'!
- !Importer commentStamp!
- I can import Amber code from a string in the chunk format.
- ## API
- Importer new import: aString!
- !Importer methodsFor: 'accessing'!
- lastChunk
- ^ lastChunk
- !
- lastSection
- ^ lastSection
- ! !
- !Importer methodsFor: 'fileIn'!
- import: aStream
- | chunk result parser lastEmpty |
- parser := ChunkParser on: aStream.
- lastEmpty := false.
- lastSection := 'n/a, not started'.
- lastChunk := nil.
- [
- [ chunk := parser nextChunk.
- chunk isNil ] whileFalse: [
- chunk isEmpty
- ifTrue: [ lastEmpty := true ]
- ifFalse: [
- lastSection := chunk.
- result := Compiler new evaluateExpression: chunk.
- lastEmpty
- ifTrue: [
- lastEmpty := false.
- result scanFrom: parser ]] ].
- lastSection := 'n/a, finished'
- ] on: Error do: [:e | lastChunk := parser last. e resignal ].
- ! !
- Error subclass: #PackageCommitError
- instanceVariableNames: ''
- package: 'Platform-ImportExport'!
- !PackageCommitError commentStamp!
- I get signaled when an attempt to commit a package has failed.!
- InterfacingObject subclass: #PackageHandler
- instanceVariableNames: ''
- package: 'Platform-ImportExport'!
- !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
- self subclassResponsibility
- ! !
- !PackageHandler methodsFor: 'committing'!
- commit: aPackage
- self
- commit: aPackage
- onSuccess: []
- onError: [ :error |
- PackageCommitError new
- messageText: 'Commiting failed with reason: "' , (error responseText) , '"';
- signal ]
- !
- commit: aPackage onSuccess: aBlock onError: anotherBlock
- self
- commitJsFileFor: aPackage
- onSuccess: [
- self
- commitStFileFor: aPackage
- onSuccess: [ aPackage beClean. aBlock value ]
- onError: anotherBlock ]
- onError: anotherBlock
- !
- commitJsFileFor: aPackage onSuccess: aBlock onError: anotherBlock
- self
- ajaxPutAt: (self commitPathJsFor: aPackage), '/', aPackage name, '.js'
- data: (self contentsFor: aPackage)
- onSuccess: aBlock
- onError: anotherBlock
- !
- commitStFileFor: aPackage onSuccess: aBlock onError: anotherBlock
- self
- ajaxPutAt: (self commitPathStFor: aPackage), '/', aPackage name, '.st'
- data: (self chunkContentsFor: aPackage)
- onSuccess: aBlock
- onError: anotherBlock
- ! !
- !PackageHandler methodsFor: 'error handling'!
- onCommitError: anError
- PackageCommitError new
- messageText: 'Commiting failed with reason: "' , (anError responseText) , '"';
- signal
- ! !
- !PackageHandler methodsFor: 'factory'!
- chunkExporter
- ^ self chunkExporterClass new
- !
- exporter
- ^ self exporterClass new
- ! !
- !PackageHandler methodsFor: 'loading'!
- load: aPackage
- self subclassResponsibility
- ! !
- !PackageHandler methodsFor: 'private'!
- ajaxPutAt: aURL data: aString onSuccess: aBlock onError: anotherBlock
- self
- ajax: #{
- 'url' -> aURL.
- 'type' -> 'PUT'.
- 'data' -> aString.
- 'contentType' -> 'text/plain;charset=UTF-8'.
- 'success' -> aBlock.
- 'error' -> anotherBlock
- }
- ! !
- PackageHandler subclass: #AmdPackageHandler
- instanceVariableNames: ''
- package: 'Platform-ImportExport'!
- !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 will be committed to .js path.
- It is recommended not to use _source as it can be deprecated."
-
- | path pathWithout |
- path := self toUrl: (self namespaceFor: aPackage), '/_source'.
- pathWithout := self commitPathJsFor: aPackage.
- ^ path = (pathWithout, '/_source') ifTrue: [ pathWithout ] ifFalse: [ path ]
- !
- exporterClass
- ^ AmdExporter
- ! !
- !AmdPackageHandler methodsFor: 'committing'!
- namespaceFor: aPackage
- ^ aPackage transport namespace
- ! !
- !AmdPackageHandler methodsFor: 'loading'!
- load: aPackage
- Smalltalk amdRequire
- ifNil: [ self error: 'AMD loader not present' ]
- ifNotNil: [ :require |
- require value: (Array with: (self namespaceFor: aPackage), '/', aPackage name ) ]
- ! !
- !AmdPackageHandler methodsFor: 'private'!
- toUrl: aString
- ^ Smalltalk amdRequire
- ifNil: [ self error: 'AMD loader not present' ]
- ifNotNil: [ :require | (require basicAt: 'toUrl') value: aString ]
- ! !
- !AmdPackageHandler class methodsFor: 'commit paths'!
- defaultNamespace
- ^ Smalltalk defaultAmdNamespace
- !
- defaultNamespace: aString
- Smalltalk defaultAmdNamespace: aString
- ! !
- Object subclass: #PackageTransport
- instanceVariableNames: 'package'
- package: 'Platform-ImportExport'!
- !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
- !
- definition
- ^ ''
- !
- package
- ^ package
- !
- package: aPackage
- package := aPackage
- !
- type
- ^ self class type
- ! !
- !PackageTransport methodsFor: 'committing'!
- commit
- self commitHandler commit: self package
- !
- commitOnSuccess: aBlock onError: anotherBlock
- self commitHandler
- commit: self package
- onSuccess: aBlock
- onError: anotherBlock
- ! !
- !PackageTransport methodsFor: 'converting'!
- asJSON
- ^ #{ 'type' -> self type }
- ! !
- !PackageTransport methodsFor: 'factory'!
- commitHandler
- ^ self commitHandlerClass new
- ! !
- !PackageTransport methodsFor: 'initialization'!
- setupFromJson: anObject
- "no op. override if needed in subclasses"
- ! !
- !PackageTransport methodsFor: 'loading'!
- load
- self commitHandler load: self package
- ! !
- PackageTransport class instanceVariableNames: 'registry'!
- !PackageTransport class methodsFor: 'accessing'!
- classRegisteredFor: aString
- ^ registry at: aString
- !
- defaultType
- ^ AmdPackageTransport type
- !
- type
- "Override in subclasses"
- ^ nil
- ! !
- !PackageTransport class methodsFor: 'initialization'!
- initialize
- super initialize.
- self == PackageTransport
- ifTrue: [ registry := #{} ]
- ifFalse: [ self register ]
- ! !
- !PackageTransport class methodsFor: 'instance creation'!
- for: aString
- ^ (self classRegisteredFor: aString) new
- !
- fromJson: anObject
- anObject ifNil: [ ^ self for: self defaultType ].
-
- ^ (self for: anObject type)
- setupFromJson: anObject;
- yourself
- ! !
- !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: 'Platform-ImportExport'!
- !AmdPackageTransport commentStamp!
- I am the default transport for committing packages.
- See `AmdExporter` and `AmdPackageHandler`.!
- !AmdPackageTransport methodsFor: 'accessing'!
- commitHandlerClass
- ^ AmdPackageHandler
- !
- definition
- ^ String streamContents: [ :stream |
- stream
- nextPutAll: self class name;
- nextPutAll: ' namespace: ';
- nextPutAll: '''', self namespace, '''' ]
- !
- namespace
- ^ namespace ifNil: [ self defaultNamespace ]
- !
- namespace: aString
- namespace := aString
- ! !
- !AmdPackageTransport methodsFor: 'actions'!
- setPath: aString
- "Set the path the the receiver's `namespace`"
-
- (require basicAt: 'config') value: #{
- 'paths' -> #{
- self namespace -> aString
- }
- }.
- ! !
- !AmdPackageTransport methodsFor: 'converting'!
- asJSON
- ^ super asJSON
- at: 'amdNamespace' put: self namespace;
- yourself
- ! !
- !AmdPackageTransport methodsFor: 'defaults'!
- defaultNamespace
- ^ Smalltalk defaultAmdNamespace
- ! !
- !AmdPackageTransport methodsFor: 'initialization'!
- setupFromJson: anObject
- self namespace: (anObject at: 'amdNamespace')
- ! !
- !AmdPackageTransport methodsFor: 'printing'!
- printOn: aStream
- super printOn: aStream.
- aStream
- nextPutAll: ' (AMD Namespace: ';
- nextPutAll: self namespace;
- nextPutAll: ')'
- ! !
- !AmdPackageTransport class methodsFor: 'accessing'!
- type
- ^ 'amd'
- ! !
- !AmdPackageTransport class methodsFor: 'instance creation'!
- namespace: aString
- ^ self new
- namespace: aString;
- yourself
- ! !
- !Behavior methodsFor: '*Platform-ImportExport'!
- commentStamp
- ^ ClassCommentReader new
- class: self;
- yourself
- !
- commentStamp: aStamp prior: prior
- ^ self commentStamp
- !
- methodsFor: aString
- ^ ClassProtocolReader new
- class: self category: aString;
- yourself
- !
- methodsFor: aString stamp: aStamp
- "Added for file-in compatibility, ignores stamp."
- ^ self methodsFor: aString
- ! !
- !Package methodsFor: '*Platform-ImportExport'!
- commit
- ^ self transport commit
- !
- load
- ^ self transport load
- !
- loadFromNamespace: aString
- ^ self transport
- namespace: aString;
- load
- ! !
- !Package class methodsFor: '*Platform-ImportExport'!
- load: aPackageName
- (self named: aPackageName) load
- !
- load: aPackageName fromNamespace: aString
- (self named: aPackageName) loadFromNamespace: aString
- ! !
|