123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951 |
- Smalltalk current createPackage: 'Importer-Exporter'!
- Object subclass: #AbstractExporter
- instanceVariableNames: ''
- package: 'Importer-Exporter'!
- !AbstractExporter commentStamp!
- I am an abstract exporter for Amber source code.!
- !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: 'fileOut'!
- recipe
- "Recipe to export a given package."
- self subclassResponsibility
- ! !
- AbstractExporter class instanceVariableNames: 'default'!
- !AbstractExporter class methodsFor: 'instance creation'!
- default
- ^ default ifNil: [ default := self new ]
- ! !
- 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 aClassthat are not package extensions"
-
- "Issue #143: sort protocol alphabetically"
- | map |
- map := Dictionary new.
- aClass protocolsDo: [:category :methods |
- (category match: '^\*') ifFalse: [ map at: category put: methods ]].
- ^(map keys sorted: [:a :b | a <= b ]) collect: [:category |
- MethodCategory name: category theClass: aClass methods: (map at: category) ]
- !
- ownCategoriesOfMetaClass: aClass
- "Issue #143: sort protocol alphabetically"
- ^self ownCategoriesOfClass: aClass class
- ! !
- !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: '!!'
- !
- exportPackageDefinitionOf: aPackage on: aStream
- "Chunk format."
- aStream
- nextPutAll: 'Smalltalk current createPackage: ''', aPackage name, '''!!';
- lf
- ! !
- 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 case
- I am typically used to save code outside of the Amber runtime (committing to disk, etc.).
- ## API
- Use `#exportAll`, `#exportClass:` or `#exportPackage:` methods.!
- !Exporter methodsFor: 'accessing'!
- extensionMethodsOfPackage: aPackage
- "Issue #143: sort classes and methods alphabetically"
- | name result |
- name := aPackage name.
- result := OrderedCollection new.
- (Package sortedClasses: Smalltalk current classes) do: [:each |
- {each. each class} do: [:aClass |
- result addAll: (((aClass methodDictionary values)
- sorted: [:a :b | a selector <= b selector])
- select: [:method | method category = ('*', name)]) ]].
- ^result
- !
- 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
- !
- 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: #StrippedExporter
- instanceVariableNames: ''
- package: 'Importer-Exporter'!
- !StrippedExporter commentStamp!
- I export Amber code into a JavaScript string, but without any optional associated data like the Amber source code.!
- !StrippedExporter 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: ');'.
- aStream 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: 'fn: ', aMethod fn compiledSource, ',';lf;
- nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;
- nextPutAll: '}),';lf;
- nextPutAll: 'smalltalk.', (self classNameFor: aMethod methodClass);
- nextPutAll: ');';lf;lf
- ! !
- Object subclass: #AmdExporter
- instanceVariableNames: ''
- package: 'Importer-Exporter'!
- !AmdExporter class methodsFor: 'exporting-output'!
- exportPackageEpilogueOf: aPackage on: aStream
- aStream
- nextPutAll: '});';
- lf
- !
- exportPackagePrologueOf: aPackage on: aStream
- aStream
- nextPutAll: 'define("';
- nextPutAll: (aPackage amdNamespace ifNil: [ 'amber' ]); "ifNil: only for LegacyPH, it should not happen with AmdPH"
- 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 class methodsFor: 'private'!
- amdNamesOfPackages: anArray
- | deps depNames |
- ^(anArray
- select: [ :each | each amdNamespace notNil ])
- collect: [ :each | each amdNamespace, '/', each name ]
- ! !
- 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 metod 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: #ExportRecipeInterpreter
- instanceVariableNames: ''
- package: 'Importer-Exporter'!
- !ExportRecipeInterpreter commentStamp!
- I am an interpreter for export recipes.
- ## Recipe format
- Recipe is an array, which can contain two kinds of elements:
- - an assocation where the key is the receiver and the value is a two-arguments selector
- In this case, `receiver perform: selector withArguments: { data. stream }` is called.
- This essentially defines one step of export process.
- The key (eg. receiver) is presumed to be some kind of 'repository' of the exporting methods
- that just format appropriate aspect of data into a stream; like a class or a singleton,
- so that the recipe itself can be decoupled from data.
- - a subarray, where first element is special and the rest is recursive recipe.
- `subarray first` must be an association similar to one above,
- with key being the 'repository' receiver, but value is one-arg selector.
- In this case, `receiver perform: selector withArguments: { data }` should create a collection.
- Then, the sub-recipe (`subarray allButFirst`) is applied to every element of a collection, eg.
- collection do: [ :each | self export: each using: sa allButFirst on: stream ]!
- !ExportRecipeInterpreter methodsFor: 'interpreting'!
- interpret: aRecipe for: anObject on: aStream
- | recipeStream |
-
- recipeStream := aRecipe readStream.
-
- [ recipeStream atEnd ] whileFalse: [
- self
- interpretStep: recipeStream next
- for: anObject
- on: aStream ]
- !
- interpretStep: aRecipeStep for: anObject on: aStream
- aRecipeStep value == aRecipeStep ifTrue: [
- ^ self interpretSubRecipe: aRecipeStep for: anObject on: aStream ].
-
- aRecipeStep key perform: aRecipeStep value withArguments: { anObject. aStream }
- !
- interpretSubRecipe: aRecipe for: anObject on: aStream
- | selection |
- selection := aRecipe first key
- perform: aRecipe first value
- withArguments: { anObject }.
- selection do: [ :each |
- self interpret: aRecipe allButFirst for: each on: aStream ]
- ! !
- 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: 'committing'!
- commit: 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
- !
- commitChannels
- self subclassResponsibility
- ! !
- !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 class instanceVariableNames: 'registry'!
- !PackageHandler class methodsFor: 'accessing'!
- classRegisteredFor: aString
- ^registry at: aString
- !
- for: aString
- ^(self classRegisteredFor: aString) new
- ! !
- !PackageHandler class methodsFor: 'initialization'!
- initialize
- super initialize.
- registry := #{}
- ! !
- !PackageHandler class methodsFor: 'registry'!
- register: aClass for: aString
- registry at: aString put: aClass
- !
- registerFor: aString
- PackageHandler register: self for: aString
- ! !
- 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: 'committing'!
- commitChannels
- ^{
- [ :pkg | Exporter default amdRecipe -> (pkg commitPathJs, '/', pkg name, '.js') ].
- [ :pkg | StrippedExporter default amdRecipe -> (pkg commitPathJs, '/', pkg name, '.deploy.js') ].
- [ :pkg | ChunkExporter default recipe -> (pkg commitPathSt, '/', pkg name, '.st') ]
- }
- !
- 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'.
- !
- namespaceFor: aPackage
- ^aPackage amdNamespace
- ifNil: [ aPackage amdNamespace: self class defaultNamespace; amdNamespace ]
- ! !
- !AmdPackageHandler methodsFor: 'private'!
- toUrl: aString
- (Smalltalk current at: '_amd_require')
- ifNil: [ self error: 'AMD loader not present' ]
- ifNotNil: [ :require | ^(require basicAt: 'toUrl') value: aString ]
- ! !
- AmdPackageHandler class instanceVariableNames: 'defaultNamespace'!
- !AmdPackageHandler class methodsFor: 'commit paths'!
- commitPathsFromLoader
- (Smalltalk current at: '_amd_defaultNamespace')
- ifNotNil: [ :namespace | self defaultNamespace: namespace ]
- !
- defaultNamespace
- ^ defaultNamespace ifNil: [ self error: 'AMD default namespace not set.' ]
- !
- defaultNamespace: aString
- defaultNamespace := aString
- !
- resetCommitPaths
- defaultNamespace := nil
- ! !
- !AmdPackageHandler class methodsFor: 'initialization'!
- initialize
- super initialize.
- self registerFor: 'amd'.
- self commitPathsFromLoader
- ! !
- PackageHandler subclass: #LegacyPackageHandler
- instanceVariableNames: ''
- package: 'Importer-Exporter'!
- !LegacyPackageHandler commentStamp!
- I am responsible for handling package loading and committing.
- I should not be used directly. Instead, use the corresponding `Package` methods.!
- !LegacyPackageHandler methodsFor: 'committing'!
- commitChannels
- ^{
- [ :pkg | Exporter default recipe -> (pkg commitPathJs, '/', pkg name, '.js') ].
- [ :pkg | StrippedExporter default recipe -> (pkg commitPathJs, '/', pkg name, '.deploy.js') ].
- [ :pkg | ChunkExporter default recipe -> (pkg commitPathSt, '/', pkg name, '.st') ]
- }
- !
- commitPathJsFor: aPackage
- ^self class defaultCommitPathJs
- !
- commitPathStFor: aPackage
- ^self class defaultCommitPathSt
- ! !
- !LegacyPackageHandler methodsFor: 'loading'!
- loadPackage: packageName prefix: aString
- | url |
- url := '/', aString, '/js/', packageName, '.js'.
- self
- ajax: #{
- 'url' -> url.
- 'type' -> 'GET'.
- 'dataType' -> 'script'.
- 'complete' -> [ :jqXHR :textStatus |
- jqXHR readyState = 4
- ifTrue: [ self setupPackageNamed: packageName prefix: aString ] ].
- 'error' -> [ self alert: 'Could not load package at: ', url ]
- }
- !
- loadPackages: aCollection prefix: aString
- aCollection do: [ :each |
- self loadPackage: each prefix: aString ]
- ! !
- !LegacyPackageHandler methodsFor: 'private'!
- setupPackageNamed: packageName prefix: aString
- (Package named: packageName)
- setupClasses;
- commitPathJs: '/', aString, '/js';
- commitPathSt: '/', aString, '/st'
- ! !
- LegacyPackageHandler class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
- !LegacyPackageHandler class methodsFor: 'commit paths'!
- commitPathsFromLoader
- <
- var commitPath = typeof amber !!== 'undefined' && amber.commitPath;
- if (!!commitPath) return;
- if (commitPath.js) self._defaultCommitPathJs_(commitPath.js);
- if (commitPath.st) self._defaultCommitPathSt_(commitPath.st);
- >
- !
- defaultCommitPathJs
- ^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
- !
- defaultCommitPathJs: aString
- defaultCommitPathJs := aString
- !
- defaultCommitPathSt
- ^ defaultCommitPathSt ifNil: [ defaultCommitPathSt := 'st']
- !
- defaultCommitPathSt: aString
- defaultCommitPathSt := aString
- !
- resetCommitPaths
- defaultCommitPathJs := nil.
- defaultCommitPathSt := nil
- ! !
- !LegacyPackageHandler class methodsFor: 'initialization'!
- initialize
- super initialize.
- self registerFor: 'unknown'.
- self commitPathsFromLoader
- ! !
- !LegacyPackageHandler class methodsFor: 'loading'!
- loadPackages: aCollection prefix: aString
- ^ self new loadPackages: aCollection prefix: aString
- ! !
- 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'!
- amdNamespace
- <return (self.transport && self.transport.amdNamespace) || nil>
- !
- amdNamespace: aString
- <
- if (!!self.transport) { self.transport = { type: 'amd' }; }
- if (self.transport.type !!== 'amd') { throw new Error('Package '+self._name()+' has transport type '+self.transport.type+', not "amd".'); }
- self.transport.amdNamespace = aString;
- >
- !
- commit
- ^ self transport commit: self
- !
- commitPathJs
- ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs ifAbsent: [self transport commitPathJsFor: self]
- !
- commitPathJs: aString
- ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs put: aString
- !
- commitPathSt
- ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt ifAbsent: [self transport commitPathStFor: self]
- !
- commitPathSt: aString
- ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt put: aString
- !
- transport
- ^ PackageHandler for: self transportType
- !
- transportJson
- <return JSON.stringify(self.transport || null);>
- !
- transportType
- <return (self.transport && self.transport.type) || 'unknown';>
- ! !
|