Browse Source

Export using 'slots:' API.

Herby Vojčík 5 years ago
parent
commit
1a8c7e2c72

+ 7 - 7
cli/src/AmberCli.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'AmberCli'!
 Object subclass: #AmberCli
-	instanceVariableNames: ''
+	slots: {}
 	package: 'AmberCli'!
 !AmberCli commentStamp!
 I am the Amber CLI (CommandLine Interface) tool which runs on Node.js.
@@ -99,7 +99,7 @@ main
 ! !
 
 Object subclass: #BaseFileManipulator
-	instanceVariableNames: 'path fs'
+	slots: {#path. #fs}
 	package: 'AmberCli'!
 
 !BaseFileManipulator methodsFor: 'initialization'!
@@ -121,7 +121,7 @@ rootDirname
 ! !
 
 BaseFileManipulator subclass: #Configurator
-	instanceVariableNames: ''
+	slots: {}
 	package: 'AmberCli'!
 
 !Configurator methodsFor: 'action'!
@@ -146,7 +146,7 @@ initialize
 ! !
 
 BaseFileManipulator subclass: #FileServer
-	instanceVariableNames: 'http url host port basePath util username password fallbackPage'
+	slots: {#http. #url. #host. #port. #basePath. #util. #username. #password. #fallbackPage}
 	package: 'AmberCli'!
 !FileServer commentStamp!
 I am the Amber Smalltalk FileServer.
@@ -447,7 +447,7 @@ startOn: aPort
 	self start
 ! !
 
-FileServer class instanceVariableNames: 'mimeTypes'!
+FileServer class slots: {#mimeTypes}!
 
 !FileServer class methodsFor: 'accessing'!
 
@@ -977,7 +977,7 @@ main
 ! !
 
 BaseFileManipulator subclass: #Initer
-	instanceVariableNames: 'childProcess nmPath'
+	slots: {#childProcess. #nmPath}
 	package: 'AmberCli'!
 
 !Initer methodsFor: 'action'!
@@ -1054,7 +1054,7 @@ npmScriptForModule: aString named: anotherString
 ! !
 
 Object subclass: #Repl
-	instanceVariableNames: 'readline interface util session resultCount commands'
+	slots: {#readline. #interface. #util. #session. #resultCount. #commands}
 	package: 'AmberCli'!
 !Repl commentStamp!
 I am a class representing a REPL (Read Evaluate Print Loop) and provide a command line interface to Amber Smalltalk.

+ 17 - 17
lang/src/Compiler-AST.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-AST'!
 DagParentNode subclass: #ASTNode
-	instanceVariableNames: 'parent position source shouldBeAliased'
+	slots: {#parent. #position. #source. #shouldBeAliased}
 	package: 'Compiler-AST'!
 !ASTNode commentStamp!
 I am the abstract root class of the abstract syntax tree.
@@ -171,7 +171,7 @@ requiresSmalltalkContext
 ! !
 
 ASTNode subclass: #AssignmentNode
-	instanceVariableNames: 'left right'
+	slots: {#left. #right}
 	package: 'Compiler-AST'!
 !AssignmentNode commentStamp!
 I represent an assignment node.!
@@ -211,7 +211,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #BlockNode
-	instanceVariableNames: 'parameters scope'
+	slots: {#parameters. #scope}
 	package: 'Compiler-AST'!
 !BlockNode commentStamp!
 I represent an block closure node.!
@@ -247,7 +247,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #CascadeNode
-	instanceVariableNames: 'receiver'
+	slots: {#receiver}
 	package: 'Compiler-AST'!
 !CascadeNode commentStamp!
 I represent an cascade node.!
@@ -275,7 +275,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #DynamicArrayNode
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !DynamicArrayNode commentStamp!
 I represent an dynamic array node.!
@@ -287,7 +287,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #DynamicDictionaryNode
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !DynamicDictionaryNode commentStamp!
 I represent an dynamic dictionary node.!
@@ -299,7 +299,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #JSStatementNode
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !JSStatementNode commentStamp!
 I represent an JavaScript statement node.!
@@ -321,7 +321,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #MethodNode
-	instanceVariableNames: 'selector arguments source scope classReferences sendIndexes'
+	slots: {#selector. #arguments. #source. #scope. #classReferences. #sendIndexes}
 	package: 'Compiler-AST'!
 !MethodNode commentStamp!
 I represent an method node.
@@ -400,7 +400,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #ReturnNode
-	instanceVariableNames: 'scope'
+	slots: {#scope}
 	package: 'Compiler-AST'!
 !ReturnNode commentStamp!
 I represent an return node. At the AST level, there is not difference between a local return or non-local return.!
@@ -432,7 +432,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #SendNode
-	instanceVariableNames: 'selector arguments receiver index shouldBeInlined'
+	slots: {#selector. #arguments. #receiver. #index. #shouldBeInlined}
 	package: 'Compiler-AST'!
 !SendNode commentStamp!
 I represent an message send node.!
@@ -516,7 +516,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ASTNode subclass: #SequenceNode
-	instanceVariableNames: 'temps pragmas scope'
+	slots: {#temps. #pragmas. #scope}
 	package: 'Compiler-AST'!
 !SequenceNode commentStamp!
 I represent an sequence node. A sequence represent a set of instructions inside the same scope (the method scope or a block scope).!
@@ -572,7 +572,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 SequenceNode subclass: #BlockSequenceNode
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !BlockSequenceNode commentStamp!
 I represent an special sequence node for block scopes.!
@@ -596,7 +596,7 @@ pragmas: aCollection
 ! !
 
 ASTNode subclass: #ValueNode
-	instanceVariableNames: 'value'
+	slots: {#value}
 	package: 'Compiler-AST'!
 !ValueNode commentStamp!
 I represent a value node.!
@@ -628,7 +628,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ValueNode subclass: #VariableNode
-	instanceVariableNames: 'assigned binding'
+	slots: {#assigned. #binding}
 	package: 'Compiler-AST'!
 !VariableNode commentStamp!
 I represent an variable node.!
@@ -693,13 +693,13 @@ acceptDagVisitor: aVisitor
 ! !
 
 Error subclass: #CompilerError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !CompilerError commentStamp!
 I am the common superclass of all compiling errors.!
 
 PathDagVisitor subclass: #ParentFakingPathDagVisitor
-	instanceVariableNames: 'setParentSelector'
+	slots: {#setParentSelector}
 	package: 'Compiler-AST'!
 !ParentFakingPathDagVisitor commentStamp!
 I am base class of `DagNode` visitor.
@@ -715,7 +715,7 @@ visit: aNode
 ! !
 
 ParentFakingPathDagVisitor subclass: #NodeVisitor
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-AST'!
 !NodeVisitor commentStamp!
 I am the abstract super class of all AST node visitors.!

+ 7 - 7
lang/src/Compiler-Core.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-Core'!
 Object subclass: #AbstractCodeGenerator
-	instanceVariableNames: 'currentClass currentPackage source'
+	slots: {#currentClass. #currentPackage. #source}
 	package: 'Compiler-Core'!
 !AbstractCodeGenerator commentStamp!
 I am the abstract super class of all code generators and provide their common API.!
@@ -54,7 +54,7 @@ transformersDictionary
 ! !
 
 AbstractCodeGenerator subclass: #CodeGenerator
-	instanceVariableNames: 'transformersDictionary'
+	slots: {#transformersDictionary}
 	package: 'Compiler-Core'!
 !CodeGenerator commentStamp!
 I am a basic code generator. I generate a valid JavaScript output, but no not perform any inlining.
@@ -95,7 +95,7 @@ translator
 ! !
 
 Object subclass: #Compiler
-	instanceVariableNames: 'currentClass currentPackage source codeGeneratorClass codeGenerator'
+	slots: {#currentClass. #currentPackage. #source. #codeGeneratorClass. #codeGenerator}
 	package: 'Compiler-Core'!
 !Compiler commentStamp!
 I provide the public interface for compiling Amber source code into JavaScript.
@@ -271,13 +271,13 @@ eval: aString
 ! !
 
 Object subclass: #DoIt
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Core'!
 !DoIt commentStamp!
 `DoIt` is the class used to compile and evaluate expressions. See `Compiler >> evaluateExpression:`.!
 
 Object subclass: #Evaluator
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Core'!
 !Evaluator commentStamp!
 I evaluate code against a receiver, dispatching #evaluate:on: to the receiver.!
@@ -325,7 +325,7 @@ evaluate: aString for: anObject
 ! !
 
 NodeVisitor subclass: #Pragmator
-	instanceVariableNames: 'methodNode sequenceNode'
+	slots: {#methodNode. #sequenceNode}
 	package: 'Compiler-Core'!
 !Pragmator commentStamp!
 I am abstract superclass for pragma-processing transformer.
@@ -385,7 +385,7 @@ visitSequenceNode: aNode
 ! !
 
 Pragmator subclass: #EarlyPragmator
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Core'!
 
 !String methodsFor: '*Compiler-Core'!

+ 22 - 22
lang/src/Compiler-IR.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-IR'!
 NodeVisitor subclass: #IRASTTranslator
-	instanceVariableNames: 'source theClass method sequence nextAlias'
+	slots: {#source. #theClass. #method. #sequence. #nextAlias}
 	package: 'Compiler-IR'!
 !IRASTTranslator commentStamp!
 I am the AST (abstract syntax tree) visitor responsible for building the intermediate representation graph.!
@@ -260,7 +260,7 @@ visitVariableNode: aNode
 ! !
 
 DagParentNode subclass: #IRInstruction
-	instanceVariableNames: 'parent'
+	slots: {#parent}
 	package: 'Compiler-IR'!
 !IRInstruction commentStamp!
 I am the abstract root class of the IR (intermediate representation) instructions class hierarchy.
@@ -362,7 +362,7 @@ on: aBuilder
 ! !
 
 IRInstruction subclass: #IRAssignment
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRAssignment methodsFor: 'accessing'!
@@ -382,7 +382,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRDynamicArray
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRDynamicArray methodsFor: 'visiting'!
@@ -392,7 +392,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRDynamicDictionary
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRDynamicDictionary methodsFor: 'visiting'!
@@ -402,7 +402,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRScopedInstruction
-	instanceVariableNames: 'scope'
+	slots: {#scope}
 	package: 'Compiler-IR'!
 
 !IRScopedInstruction methodsFor: 'accessing'!
@@ -416,7 +416,7 @@ scope: aScope
 ! !
 
 IRScopedInstruction subclass: #IRClosureInstruction
-	instanceVariableNames: 'arguments requiresSmalltalkContext'
+	slots: {#arguments. #requiresSmalltalkContext}
 	package: 'Compiler-IR'!
 
 !IRClosureInstruction methodsFor: 'accessing'!
@@ -454,7 +454,7 @@ tempDeclarations
 ! !
 
 IRClosureInstruction subclass: #IRClosure
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRClosure methodsFor: 'accessing'!
@@ -476,7 +476,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRClosureInstruction subclass: #IRMethod
-	instanceVariableNames: 'theClass source selector classReferences sendIndexes requiresSmalltalkContext internalVariables'
+	slots: {#theClass. #source. #selector. #classReferences. #sendIndexes. #requiresSmalltalkContext. #internalVariables}
 	package: 'Compiler-IR'!
 !IRMethod commentStamp!
 I am a method instruction!
@@ -548,7 +548,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRScopedInstruction subclass: #IRReturn
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 !IRReturn commentStamp!
 I am a local return instruction.!
@@ -576,7 +576,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRReturn subclass: #IRBlockReturn
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 !IRBlockReturn commentStamp!
 Smalltalk blocks return their last statement. I am a implicit block return instruction.!
@@ -588,7 +588,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRReturn subclass: #IRNonLocalReturn
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 !IRNonLocalReturn commentStamp!
 I am a non local return instruction.
@@ -603,7 +603,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRScopedInstruction subclass: #IRTempDeclaration
-	instanceVariableNames: 'name'
+	slots: {#name}
 	package: 'Compiler-IR'!
 
 !IRTempDeclaration methodsFor: 'accessing'!
@@ -629,7 +629,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRSend
-	instanceVariableNames: 'selector index'
+	slots: {#selector. #index}
 	package: 'Compiler-IR'!
 !IRSend commentStamp!
 I am a message send instruction.!
@@ -673,7 +673,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRSequence
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRSequence methodsFor: 'testing'!
@@ -689,7 +689,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRSequence subclass: #IRBlockSequence
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRBlockSequence methodsFor: 'visiting'!
@@ -699,7 +699,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRValue
-	instanceVariableNames: 'value'
+	slots: {#value}
 	package: 'Compiler-IR'!
 !IRValue commentStamp!
 I am the simplest possible instruction. I represent a value.!
@@ -727,7 +727,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRVariable
-	instanceVariableNames: 'variable'
+	slots: {#variable}
 	package: 'Compiler-IR'!
 !IRVariable commentStamp!
 I am a variable instruction.!
@@ -767,7 +767,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInstruction subclass: #IRVerbatim
-	instanceVariableNames: 'source'
+	slots: {#source}
 	package: 'Compiler-IR'!
 
 !IRVerbatim methodsFor: 'accessing'!
@@ -787,7 +787,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 ParentFakingPathDagVisitor subclass: #IRVisitor
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-IR'!
 
 !IRVisitor methodsFor: 'visiting'!
@@ -869,7 +869,7 @@ visitIRVerbatim: anIRVerbatim
 ! !
 
 IRVisitor subclass: #IRJSTranslator
-	instanceVariableNames: 'stream currentClass'
+	slots: {#stream. #currentClass}
 	package: 'Compiler-IR'!
 
 !IRJSTranslator methodsFor: 'accessing'!
@@ -1053,7 +1053,7 @@ visitSuperSend: anIRSend
 ! !
 
 Object subclass: #JSStream
-	instanceVariableNames: 'stream omitSemicolon'
+	slots: {#stream. #omitSemicolon}
 	package: 'Compiler-IR'!
 
 !JSStream methodsFor: 'accessing'!

+ 16 - 16
lang/src/Compiler-Inlining.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-Inlining'!
 NodeVisitor subclass: #ASTPreInliner
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 
 !ASTPreInliner methodsFor: 'visiting'!
@@ -17,7 +17,7 @@ visitSendNode: aNode
 ! !
 
 IRClosure subclass: #IRInlinedClosure
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedClosure commentStamp!
 I represent an inlined closure instruction.!
@@ -35,7 +35,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRSend subclass: #IRInlinedSend
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedSend commentStamp!
 I am the abstract super class of inlined message send instructions.!
@@ -62,7 +62,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInlinedSend subclass: #IRInlinedIfFalse
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedIfFalse commentStamp!
 I represent an inlined `#ifFalse:` message send instruction.!
@@ -74,7 +74,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInlinedSend subclass: #IRInlinedIfNilIfNotNil
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedIfNilIfNotNil commentStamp!
 I represent an inlined `#ifNil:ifNotNil:` message send instruction.!
@@ -102,7 +102,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInlinedSend subclass: #IRInlinedIfTrue
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedIfTrue commentStamp!
 I represent an inlined `#ifTrue:` message send instruction.!
@@ -114,7 +114,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRInlinedSend subclass: #IRInlinedIfTrueIfFalse
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedIfTrueIfFalse commentStamp!
 I represent an inlined `#ifTrue:ifFalse:` message send instruction.!
@@ -126,7 +126,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRBlockSequence subclass: #IRInlinedSequence
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInlinedSequence commentStamp!
 I represent a (block) sequence inside an inlined closure instruction (instance of `IRInlinedClosure`).!
@@ -144,7 +144,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 IRVisitor subclass: #IRInliner
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInliner commentStamp!
 I visit an IR tree, inlining message sends and block closures.
@@ -225,7 +225,7 @@ visitIRSend: anIRSend
 ! !
 
 IRJSTranslator subclass: #IRInliningJSTranslator
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRInliningJSTranslator commentStamp!
 I am a specialized JavaScript translator able to write inlined IR instructions to JavaScript stream (`JSStream` instance).!
@@ -277,7 +277,7 @@ visitIRInlinedIfTrueIfFalse: anIRInlinedIfTrueIfFalse
 ! !
 
 Object subclass: #IRSendInliner
-	instanceVariableNames: 'send translator'
+	slots: {#send. #translator}
 	package: 'Compiler-Inlining'!
 !IRSendInliner commentStamp!
 I inline some message sends and block closure arguments. I heavily rely on #perform: to dispatch inlining methods.!
@@ -470,7 +470,7 @@ shouldInline: anIRSend
 ! !
 
 IRSendInliner subclass: #IRAssignmentInliner
-	instanceVariableNames: 'target'
+	slots: {#target}
 	package: 'Compiler-Inlining'!
 !IRAssignmentInliner commentStamp!
 I inline message sends together with assignments by moving them around into the inline closure instructions.
@@ -524,7 +524,7 @@ inlineClosure: anIRClosure
 ! !
 
 IRSendInliner subclass: #IRReturnInliner
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !IRReturnInliner commentStamp!
 I inline message sends with inlined closure together with a return instruction.!
@@ -554,7 +554,7 @@ inlineReturn: anIRReturn
 ! !
 
 CodeGenerator subclass: #InliningCodeGenerator
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !InliningCodeGenerator commentStamp!
 I am a specialized code generator that uses inlining to produce more optimized JavaScript output!
@@ -582,13 +582,13 @@ transformersDictionary
 ! !
 
 SemanticError subclass: #InliningError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 !InliningError commentStamp!
 Instances of InliningError are signaled when using an `InliningCodeGenerator`in a `Compiler`.!
 
 SemanticAnalyzer subclass: #InliningSemanticAnalyzer
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Inlining'!
 
 !InliningSemanticAnalyzer methodsFor: 'visiting'!

+ 9 - 9
lang/src/Compiler-Interpreter.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-Interpreter'!
 BlockClosure subclass: #AIBlockClosure
-	instanceVariableNames: 'node outerContext'
+	slots: {#node. #outerContext}
 	package: 'Compiler-Interpreter'!
 !AIBlockClosure commentStamp!
 I am a special `BlockClosure` subclass used by an interpreter to interpret a block node.
@@ -101,7 +101,7 @@ forContext: aContext node: aNode
 ! !
 
 Object subclass: #AIContext
-	instanceVariableNames: 'outerContext innerContext pc locals selector index sendIndexes evaluatedSelector ast interpreter supercall'
+	slots: {#outerContext. #innerContext. #pc. #locals. #selector. #index. #sendIndexes. #evaluatedSelector. #ast. #interpreter. #supercall}
 	package: 'Compiler-Interpreter'!
 !AIContext commentStamp!
 I am like a `MethodContext`, used by the `ASTInterpreter`.
@@ -386,7 +386,7 @@ fromMethodContext: aMethodContext
 ! !
 
 SemanticAnalyzer subclass: #AISemanticAnalyzer
-	instanceVariableNames: 'context'
+	slots: {#context}
 	package: 'Compiler-Interpreter'!
 !AISemanticAnalyzer commentStamp!
 I perform the same semantic analysis than `SemanticAnalyzer`, with the difference that provided an `AIContext` context, variables are bound with the context variables.!
@@ -412,7 +412,7 @@ visitVariableNode: aNode
 ! !
 
 ScopeVar subclass: #ASTContextVar
-	instanceVariableNames: 'context'
+	slots: {#context}
 	package: 'Compiler-Interpreter'!
 !ASTContextVar commentStamp!
 I am a variable defined in a `context`.!
@@ -428,7 +428,7 @@ context: anObject
 ! !
 
 Object subclass: #ASTDebugger
-	instanceVariableNames: 'interpreter context result'
+	slots: {#interpreter. #context. #result}
 	package: 'Compiler-Interpreter'!
 !ASTDebugger commentStamp!
 I am a stepping debugger interface for Amber code.
@@ -539,7 +539,7 @@ context: aContext
 ! !
 
 NodeVisitor subclass: #ASTEnterNode
-	instanceVariableNames: 'interpreter'
+	slots: {#interpreter}
 	package: 'Compiler-Interpreter'!
 
 !ASTEnterNode methodsFor: 'accessing'!
@@ -581,7 +581,7 @@ on: anInterpreter
 ! !
 
 NodeVisitor subclass: #ASTInterpreter
-	instanceVariableNames: 'node context stack returnValue returned forceAtEnd'
+	slots: {#node. #context. #stack. #returnValue. #returned. #forceAtEnd}
 	package: 'Compiler-Interpreter'!
 !ASTInterpreter commentStamp!
 I visit an AST, interpreting (evaluating) nodes one after the other, using a small stack machine.
@@ -907,13 +907,13 @@ visitVariableNode: aNode
 ! !
 
 Error subclass: #ASTInterpreterError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Interpreter'!
 !ASTInterpreterError commentStamp!
 I get signaled when an AST interpreter is unable to interpret a node.!
 
 NodeVisitor subclass: #ASTPCNodeVisitor
-	instanceVariableNames: 'index trackedIndex selector currentNode'
+	slots: {#index. #trackedIndex. #selector. #currentNode}
 	package: 'Compiler-Interpreter'!
 !ASTPCNodeVisitor commentStamp!
 I visit an AST until I get to the current node for the `context` and answer it.

+ 15 - 15
lang/src/Compiler-Semantic.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-Semantic'!
 Object subclass: #LexicalScope
-	instanceVariableNames: 'node instruction temps args outerScope blockIndex'
+	slots: {#node. #instruction. #temps. #args. #outerScope. #blockIndex}
 	package: 'Compiler-Semantic'!
 !LexicalScope commentStamp!
 I represent a lexical scope where variable names are associated with ScopeVars
@@ -124,7 +124,7 @@ isMethodScope
 ! !
 
 LexicalScope subclass: #MethodLexicalScope
-	instanceVariableNames: 'iVars pseudoVars unknownVariables localReturn nonLocalReturns'
+	slots: {#iVars. #pseudoVars. #unknownVariables. #localReturn. #nonLocalReturns}
 	package: 'Compiler-Semantic'!
 !MethodLexicalScope commentStamp!
 I represent a method scope.!
@@ -208,7 +208,7 @@ isMethodScope
 ! !
 
 Object subclass: #ScopeVar
-	instanceVariableNames: 'scope name'
+	slots: {#scope. #name}
 	package: 'Compiler-Semantic'!
 !ScopeVar commentStamp!
 I am an entry in a LexicalScope that gets associated with variable nodes of the same name.
@@ -290,7 +290,7 @@ on: aString
 ! !
 
 ScopeVar subclass: #AliasVar
-	instanceVariableNames: 'node'
+	slots: {#node}
 	package: 'Compiler-Semantic'!
 !AliasVar commentStamp!
 I am an internally defined variable by the compiler!
@@ -312,7 +312,7 @@ isImmutable
 ! !
 
 ScopeVar subclass: #ArgVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !ArgVar commentStamp!
 I am an argument of a method or block.!
@@ -328,7 +328,7 @@ isImmutable
 ! !
 
 ScopeVar subclass: #ClassRefVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !ClassRefVar commentStamp!
 I am an class reference variable!
@@ -354,7 +354,7 @@ isImmutable
 ! !
 
 ScopeVar subclass: #InstanceVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !InstanceVar commentStamp!
 I am an instance variable of a method or block.!
@@ -370,7 +370,7 @@ isInstanceVar
 ! !
 
 ScopeVar subclass: #PseudoVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !PseudoVar commentStamp!
 I am an pseudo variable.
@@ -402,7 +402,7 @@ isSuper
 ! !
 
 ScopeVar subclass: #TempVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !TempVar commentStamp!
 I am an temporary variable of a method or block.!
@@ -414,7 +414,7 @@ isTempVar
 ! !
 
 ScopeVar subclass: #UnknownVar
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !UnknownVar commentStamp!
 I am an unknown variable. Amber uses unknown variables as JavaScript globals!
@@ -426,7 +426,7 @@ isUnknownVar
 ! !
 
 NodeVisitor subclass: #SemanticAnalyzer
-	instanceVariableNames: 'currentScope blockIndex thePackage theClass classReferences messageSends'
+	slots: {#currentScope. #blockIndex. #thePackage. #theClass. #classReferences. #messageSends}
 	package: 'Compiler-Semantic'!
 !SemanticAnalyzer commentStamp!
 I semantically analyze the abstract syntax tree and annotate it with informations such as non local returns and variable scopes.!
@@ -644,7 +644,7 @@ on: aClass
 ! !
 
 CompilerError subclass: #SemanticError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Semantic'!
 !SemanticError commentStamp!
 I represent an abstract semantic error thrown by the SemanticAnalyzer.
@@ -654,7 +654,7 @@ See my subclasses for concrete errors.
 The IDE should catch instances of Semantic error to deal with them when compiling!
 
 SemanticError subclass: #InvalidAssignmentError
-	instanceVariableNames: 'variableName'
+	slots: {#variableName}
 	package: 'Compiler-Semantic'!
 !InvalidAssignmentError commentStamp!
 I get signaled when a pseudo variable gets assigned.!
@@ -674,7 +674,7 @@ variableName: aString
 ! !
 
 SemanticError subclass: #ShadowingVariableError
-	instanceVariableNames: 'variableName'
+	slots: {#variableName}
 	package: 'Compiler-Semantic'!
 !ShadowingVariableError commentStamp!
 I get signaled when a variable in a block or method scope shadows a variable of the same name in an outer scope.!
@@ -694,7 +694,7 @@ variableName: aString
 ! !
 
 SemanticError subclass: #UnknownVariableError
-	instanceVariableNames: 'variableName'
+	slots: {#variableName}
 	package: 'Compiler-Semantic'!
 !UnknownVariableError commentStamp!
 I get signaled when a variable is not defined.

+ 10 - 10
lang/src/Compiler-Tests.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-Tests'!
 TestCase subclass: #ASTParsingTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ASTParsingTest methodsFor: 'parsing'!
@@ -13,7 +13,7 @@ parse: aString forClass: aClass
 ! !
 
 ASTParsingTest subclass: #ASTPCNodeVisitorTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ASTPCNodeVisitorTest methodsFor: 'factory'!
@@ -84,7 +84,7 @@ testNoMessageSend
 ! !
 
 ASTParsingTest subclass: #ASTPositionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ASTPositionTest methodsFor: 'tests'!
@@ -109,7 +109,7 @@ testNodeAtPosition
 ! !
 
 ASTParsingTest subclass: #CodeGeneratorTest
-	instanceVariableNames: 'receiver'
+	slots: {#receiver}
 	package: 'Compiler-Tests'!
 
 !CodeGeneratorTest methodsFor: 'accessing'!
@@ -473,7 +473,7 @@ testifTrueIfFalse
 ! !
 
 CodeGeneratorTest subclass: #ASTInterpreterTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ASTInterpreterTest methodsFor: 'private'!
@@ -518,7 +518,7 @@ should: aString receiver: anObject return: aResult
 ! !
 
 ASTInterpreterTest subclass: #ASTDebuggerTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ASTDebuggerTest methodsFor: 'private'!
@@ -551,7 +551,7 @@ interpret: aString receiver: anObject withArguments: aDictionary
 ! !
 
 CodeGeneratorTest subclass: #InliningCodeGeneratorTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !InliningCodeGeneratorTest methodsFor: 'accessing'!
@@ -561,7 +561,7 @@ codeGeneratorClass
 ! !
 
 TestCase subclass: #ScopeVarTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !ScopeVarTest methodsFor: 'tests'!
@@ -616,7 +616,7 @@ testUnknownVar
 ! !
 
 TestCase subclass: #SemanticAnalyzerTest
-	instanceVariableNames: 'analyzer'
+	slots: {#analyzer}
 	package: 'Compiler-Tests'!
 
 !SemanticAnalyzerTest methodsFor: 'running'!
@@ -756,7 +756,7 @@ testVariablesLookup
 ! !
 
 SemanticAnalyzerTest subclass: #AISemanticAnalyzerTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Compiler-Tests'!
 
 !AISemanticAnalyzerTest methodsFor: 'running'!

+ 27 - 27
lang/src/Kernel-Announcements.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Announcements'!
 Object subclass: #AnnouncementSubscription
-	instanceVariableNames: 'valuable announcementClass'
+	slots: {#valuable. #announcementClass}
 	package: 'Kernel-Announcements'!
 !AnnouncementSubscription commentStamp!
 I am a single entry in a subscription registry of an `Announcer`.
@@ -42,7 +42,7 @@ handlesAnnouncement: anAnnouncement
 ! !
 
 Object subclass: #AnnouncementValuable
-	instanceVariableNames: 'valuable receiver'
+	slots: {#valuable. #receiver}
 	package: 'Kernel-Announcements'!
 !AnnouncementValuable commentStamp!
 I wrap `valuable` objects (typically instances of `BlockClosure`) with a `receiver` to be able to unregister subscriptions based on a `receiver`.!
@@ -76,7 +76,7 @@ value: anObject
 ! !
 
 Object subclass: #Announcer
-	instanceVariableNames: 'registry subscriptions'
+	slots: {#registry. #subscriptions}
 	package: 'Kernel-Announcements'!
 !Announcer commentStamp!
 I hold annoncement subscriptions (instances of `AnnouncementSubscription`) in a private registry.
@@ -157,7 +157,7 @@ unsubscribe: anObject
 ! !
 
 Announcer subclass: #SystemAnnouncer
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !SystemAnnouncer commentStamp!
 My unique instance is the global announcer handling all Amber system-related announces.
@@ -166,7 +166,7 @@ My unique instance is the global announcer handling all Amber system-related ann
 
 Access to the unique instance is done via `#current`!
 
-SystemAnnouncer class instanceVariableNames: 'current'!
+SystemAnnouncer class slots: {#current}!
 
 !SystemAnnouncer class methodsFor: 'accessing'!
 
@@ -181,7 +181,7 @@ new
 ! !
 
 Object subclass: #SystemAnnouncement
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !SystemAnnouncement commentStamp!
 I am the superclass of all system announcements!
@@ -197,7 +197,7 @@ classTag
 ! !
 
 SystemAnnouncement subclass: #ClassAnnouncement
-	instanceVariableNames: 'theClass'
+	slots: {#theClass}
 	package: 'Kernel-Announcements'!
 !ClassAnnouncement commentStamp!
 I am the abstract superclass of class-related announcements.!
@@ -213,27 +213,27 @@ theClass: aClass
 ! !
 
 ClassAnnouncement subclass: #ClassAdded
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ClassAdded commentStamp!
 I am emitted when a class is added to the system.
 See ClassBuilder >> #addSubclassOf:... methods!
 
 ClassAnnouncement subclass: #ClassCommentChanged
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ClassCommentChanged commentStamp!
 I am emitted when the comment of a class changes. (Behavior >> #comment)!
 
 ClassAnnouncement subclass: #ClassDefinitionChanged
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ClassDefinitionChanged commentStamp!
 I am emitted when the definition of a class changes.
 See ClassBuilder >> #class:instanceVariableNames:!
 
 ClassAnnouncement subclass: #ClassMigrated
-	instanceVariableNames: 'oldClass'
+	slots: {#oldClass}
 	package: 'Kernel-Announcements'!
 !ClassMigrated commentStamp!
 I am emitted when a class is migrated.!
@@ -249,7 +249,7 @@ oldClass: aClass
 ! !
 
 ClassAnnouncement subclass: #ClassMoved
-	instanceVariableNames: 'oldPackage'
+	slots: {#oldPackage}
 	package: 'Kernel-Announcements'!
 !ClassMoved commentStamp!
 I am emitted when a class is moved from one package to another.!
@@ -265,21 +265,21 @@ oldPackage: aPackage
 ! !
 
 ClassAnnouncement subclass: #ClassRemoved
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ClassRemoved commentStamp!
 I am emitted when a class is removed.
 See Smalltalk >> #removeClass:!
 
 ClassAnnouncement subclass: #ClassRenamed
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ClassRenamed commentStamp!
 I am emitted when a class is renamed.
 See ClassBuilder >> #renameClass:to:!
 
 SystemAnnouncement subclass: #MethodAnnouncement
-	instanceVariableNames: 'method'
+	slots: {#method}
 	package: 'Kernel-Announcements'!
 !MethodAnnouncement commentStamp!
 I am the abstract superclass of method-related announcements.!
@@ -295,13 +295,13 @@ method: aCompiledMethod
 ! !
 
 MethodAnnouncement subclass: #MethodAdded
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !MethodAdded commentStamp!
 I am emitted when a `CompiledMethod` is added to a class.!
 
 MethodAnnouncement subclass: #MethodModified
-	instanceVariableNames: 'oldMethod'
+	slots: {#oldMethod}
 	package: 'Kernel-Announcements'!
 !MethodModified commentStamp!
 I am emitted when a `CompiledMethod` is modified (a new method is installed). I hold a reference to the old method being replaced.!
@@ -317,7 +317,7 @@ oldMethod: aMethod
 ! !
 
 MethodAnnouncement subclass: #MethodMoved
-	instanceVariableNames: 'oldProtocol'
+	slots: {#oldProtocol}
 	package: 'Kernel-Announcements'!
 !MethodMoved commentStamp!
 I am emitted when a `CompiledMethod` is moved to another protocol. I hold a refernce to the old protocol of the method.!
@@ -333,13 +333,13 @@ oldProtocol: aString
 ! !
 
 MethodAnnouncement subclass: #MethodRemoved
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !MethodRemoved commentStamp!
 I am emitted when a `CompiledMethod` is removed from a class.!
 
 SystemAnnouncement subclass: #PackageAnnouncement
-	instanceVariableNames: 'package'
+	slots: {#package}
 	package: 'Kernel-Announcements'!
 !PackageAnnouncement commentStamp!
 I am the abstract superclass of package-related announcements.!
@@ -355,31 +355,31 @@ package: aPackage
 ! !
 
 PackageAnnouncement subclass: #PackageAdded
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !PackageAdded commentStamp!
 I am emitted when a `Package` is added to the system.!
 
 PackageAnnouncement subclass: #PackageClean
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !PackageClean commentStamp!
 I am emitted when a package is committed and becomes clean.!
 
 PackageAnnouncement subclass: #PackageDirty
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !PackageDirty commentStamp!
 I am emitted when a package becomes dirty.!
 
 PackageAnnouncement subclass: #PackageRemoved
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !PackageRemoved commentStamp!
 I am emitted when a `Package` is removed from the system.!
 
 SystemAnnouncement subclass: #ProtocolAnnouncement
-	instanceVariableNames: 'theClass protocol'
+	slots: {#theClass. #protocol}
 	package: 'Kernel-Announcements'!
 !ProtocolAnnouncement commentStamp!
 I am the abstract superclass of protocol-related announcements.!
@@ -408,13 +408,13 @@ theClass: aClass
 ! !
 
 ProtocolAnnouncement subclass: #ProtocolAdded
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ProtocolAdded commentStamp!
 I am emitted when a protocol is added to a class.!
 
 ProtocolAnnouncement subclass: #ProtocolRemoved
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Announcements'!
 !ProtocolRemoved commentStamp!
 I am emitted when a protocol is removed from a class.!

+ 6 - 14
lang/src/Kernel-Classes.js

@@ -754,14 +754,10 @@ $recv(stream)._tab();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["tab"]=2;
 //>>excludeEnd("ctx");
-$recv(stream)._write_("instanceVariableNames: ");
+$recv(stream)._write_(["slots: {",". "._join_($recv($self._instanceVariableNames())._collect_("symbolPrintString")),"}"]);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["write:"]=3;
 //>>excludeEnd("ctx");
-$recv(stream)._print_(" "._join_($self._instanceVariableNames()));
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["print:"]=2;
-//>>excludeEnd("ctx");
 $recv(stream)._lf();
 $recv(stream)._tab();
 $recv(stream)._write_("package: ");
@@ -776,10 +772,10 @@ return $recv(stream)._print_($self._category());
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "definition\x0a\x09^ String streamContents: [ :stream | stream\x0a\x09\x09print: self superclass; write: ' subclass: '; printSymbol: self name; lf;\x0a\x09\x09write: (self traitCompositionDefinition ifNotEmpty: [ :tcd | { String tab. 'uses: '. tcd. String lf }]);\x0a\x09\x09tab; write: 'instanceVariableNames: '; print: (' ' join: self instanceVariableNames); lf;\x0a\x09\x09tab; write: 'package: '; print: self category ]",
+source: "definition\x0a\x09^ String streamContents: [ :stream | stream\x0a\x09\x09print: self superclass; write: ' subclass: '; printSymbol: self name; lf;\x0a\x09\x09write: (self traitCompositionDefinition ifNotEmpty: [ :tcd | { String tab. 'uses: '. tcd. String lf }]);\x0a\x09\x09tab; write: {'slots: {'. ('. ' join: (self instanceVariableNames collect: #symbolPrintString)). '}'}; lf;\x0a\x09\x09tab; write: 'package: '; print: self category ]",
 referencedClasses: ["String"],
 //>>excludeEnd("ide");
-messageSends: ["streamContents:", "print:", "superclass", "write:", "printSymbol:", "name", "lf", "ifNotEmpty:", "traitCompositionDefinition", "tab", "join:", "instanceVariableNames", "category"]
+messageSends: ["streamContents:", "print:", "superclass", "write:", "printSymbol:", "name", "lf", "ifNotEmpty:", "traitCompositionDefinition", "tab", "join:", "collect:", "instanceVariableNames", "category"]
 }),
 $globals.Class);
 
@@ -961,9 +957,6 @@ return $recv($globals.String)._streamContents_((function(stream){
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
 $recv(stream)._print_(self);
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["print:"]=1;
-//>>excludeEnd("ctx");
 $recv(stream)._write_($recv($self._traitCompositionDefinition())._ifEmpty_ifNotEmpty_((function(){
 return " ";
 
@@ -987,8 +980,7 @@ return [$1,$2,"uses: ",tcd,$recv($globals.String)._lf(),$recv($globals.String)._
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["write:"]=1;
 //>>excludeEnd("ctx");
-$recv(stream)._write_("instanceVariableNames: ");
-return $recv(stream)._print_(" "._join_($self._instanceVariableNames()));
+return $recv(stream)._write_(["slots: {",". "._join_($recv($self._instanceVariableNames())._collect_("symbolPrintString")),"}"]);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx2) {$ctx2.fillBlock({stream:stream},$ctx1,1)});
 //>>excludeEnd("ctx");
@@ -999,10 +991,10 @@ return $recv(stream)._print_(" "._join_($self._instanceVariableNames()));
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "definition\x0a\x09^ String streamContents: [ :stream | stream\x0a\x09\x09print: self;\x0a\x09\x09write: (self traitCompositionDefinition\x0a\x09\x09\x09ifEmpty: [' ']\x0a\x09\x09\x09ifNotEmpty: [ :tcd | { String lf. String tab. 'uses: '. tcd. String lf. String tab }]);\x0a\x09\x09write: 'instanceVariableNames: ';\x0a\x09\x09print: (' ' join: self instanceVariableNames) ]",
+source: "definition\x0a\x09^ String streamContents: [ :stream | stream\x0a\x09\x09print: self;\x0a\x09\x09write: (self traitCompositionDefinition\x0a\x09\x09\x09ifEmpty: [' ']\x0a\x09\x09\x09ifNotEmpty: [ :tcd | { String lf. String tab. 'uses: '. tcd. String lf. String tab }]);\x0a\x09\x09write: {'slots: {'. ('. ' join: (self instanceVariableNames collect: #symbolPrintString)). '}'} ]",
 referencedClasses: ["String"],
 //>>excludeEnd("ide");
-messageSends: ["streamContents:", "print:", "write:", "ifEmpty:ifNotEmpty:", "traitCompositionDefinition", "lf", "tab", "join:", "instanceVariableNames"]
+messageSends: ["streamContents:", "print:", "write:", "ifEmpty:ifNotEmpty:", "traitCompositionDefinition", "lf", "tab", "join:", "collect:", "instanceVariableNames"]
 }),
 $globals.Metaclass);
 

+ 9 - 10
lang/src/Kernel-Classes.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Classes'!
 Object subclass: #Behavior
-	instanceVariableNames: 'organization slots fn superclass'
+	slots: {#organization. #slots. #fn. #superclass}
 	package: 'Kernel-Classes'!
 !Behavior commentStamp!
 I am the superclass of all class objects.
@@ -153,7 +153,7 @@ isBehavior
 ! !
 
 Behavior subclass: #Class
-	instanceVariableNames: 'package subclasses'
+	slots: {#package. #subclasses}
 	package: 'Kernel-Classes'!
 !Class commentStamp!
 I am __the__ class object.
@@ -179,7 +179,7 @@ definition
 	^ String streamContents: [ :stream | stream
 		print: self superclass; write: ' subclass: '; printSymbol: self name; lf;
 		write: (self traitCompositionDefinition ifNotEmpty: [ :tcd | { String tab. 'uses: '. tcd. String lf }]);
-		tab; write: 'instanceVariableNames: '; print: (' ' join: self instanceVariableNames); lf;
+		tab; write: {'slots: {'. ('. ' join: (self instanceVariableNames collect: #symbolPrintString)). '}'}; lf;
 		tab; write: 'package: '; print: self category ]
 !
 
@@ -216,7 +216,7 @@ isClass
 ! !
 
 Behavior subclass: #Metaclass
-	instanceVariableNames: 'instanceClass'
+	slots: {#instanceClass}
 	package: 'Kernel-Classes'!
 !Metaclass commentStamp!
 I am the root of the class hierarchy.
@@ -231,8 +231,7 @@ definition
 		write: (self traitCompositionDefinition
 			ifEmpty: [' ']
 			ifNotEmpty: [ :tcd | { String lf. String tab. 'uses: '. tcd. String lf. String tab }]);
-		write: 'instanceVariableNames: ';
-		print: (' ' join: self instanceVariableNames) ]
+		write: {'slots: {'. ('. ' join: (self instanceVariableNames collect: #symbolPrintString)). '}'} ]
 !
 
 instanceClass
@@ -295,7 +294,7 @@ isMetaclass
 ! !
 
 Object subclass: #ClassBuilder
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Classes'!
 !ClassBuilder commentStamp!
 I am responsible for compiling new classes or modifying existing classes in the system.
@@ -519,7 +518,7 @@ rawRenameClass: aClass to: aString
 ! !
 
 Object subclass: #ClassSorterNode
-	instanceVariableNames: 'theClass level nodes'
+	slots: {#theClass. #level. #nodes}
 	package: 'Kernel-Classes'!
 !ClassSorterNode commentStamp!
 I provide an algorithm for sorting classes alphabetically.
@@ -916,7 +915,7 @@ asJavaScriptSource
 ! !
 
 Object subclass: #Trait
-	instanceVariableNames: 'organization package traitUsers'
+	slots: {#organization. #package. #traitUsers}
 	package: 'Kernel-Classes'!
 
 !Trait methodsFor: 'accessing'!
@@ -990,7 +989,7 @@ named: aString uses: aTraitCompositionDescription package: anotherString
 ! !
 
 Object subclass: #TraitTransformation
-	instanceVariableNames: 'trait aliases exclusions'
+	slots: {#trait. #aliases. #exclusions}
 	package: 'Kernel-Classes'!
 !TraitTransformation commentStamp!
 I am a single step in trait composition.

+ 16 - 16
lang/src/Kernel-Collections.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Collections'!
 Object subclass: #Association
-	instanceVariableNames: 'key value'
+	slots: {#key. #value}
 	package: 'Kernel-Collections'!
 !Association commentStamp!
 I represent a pair of associated objects, a key and a value. My instances can serve as entries in a dictionary.
@@ -51,7 +51,7 @@ key: aKey value: aValue
 ! !
 
 Object subclass: #BucketStore
-	instanceVariableNames: 'buckets hashBlock'
+	slots: {#buckets. #hashBlock}
 	package: 'Kernel-Collections'!
 !BucketStore commentStamp!
 I am an helper class for hash-based stores.
@@ -127,7 +127,7 @@ hashBlock: aBlock
 ! !
 
 BucketStore subclass: #ArrayBucketStore
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !ArrayBucketStore commentStamp!
 I am a concrete `BucketStore` with buckets being instance of `Array`.!
@@ -139,7 +139,7 @@ newBucket
 ! !
 
 Object subclass: #Collection
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !Collection commentStamp!
 I am the abstract superclass of all classes that represent a group of elements.
@@ -462,7 +462,7 @@ withAll: aCollection
 ! !
 
 Collection subclass: #AssociativeCollection
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !AssociativeCollection commentStamp!
 I am a base class for object-indexed collections (Dictionary et.al.).!
@@ -693,7 +693,7 @@ newFromPairs: aCollection
 ! !
 
 AssociativeCollection subclass: #Dictionary
-	instanceVariableNames: 'keys values'
+	slots: {#keys. #values}
 	package: 'Kernel-Collections'!
 !Dictionary commentStamp!
 I represent a set of elements that can be viewed from one of two perspectives: a set of associations,
@@ -806,7 +806,7 @@ includesKey: aKey
 ! !
 
 AssociativeCollection subclass: #HashedCollection
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !HashedCollection commentStamp!
 I am a traditional JavaScript object, or a Smalltalk `Dictionary`.
@@ -863,7 +863,7 @@ includesKey: aKey
 ! !
 
 Collection subclass: #SequenceableCollection
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !SequenceableCollection commentStamp!
 I am an IndexableCollection
@@ -1032,7 +1032,7 @@ streamContents: aBlock
 ! !
 
 SequenceableCollection subclass: #Array
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !Array commentStamp!
 I represent a collection of objects ordered by the collector. The size of arrays is dynamic.
@@ -1205,7 +1205,7 @@ withAll: aCollection
 ! !
 
 SequenceableCollection subclass: #String
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !String commentStamp!
 I am an indexed collection of Characters. Unlike most Smalltalk dialects, Amber doesn't provide the Character class. Instead, elements of a String are single character strings.
@@ -1639,7 +1639,7 @@ randomNotIn: aString
 ! !
 
 Collection subclass: #Set
-	instanceVariableNames: 'defaultBucket slowBucketStores fastBuckets size'
+	slots: {#defaultBucket. #slowBucketStores. #fastBuckets. #size}
 	package: 'Kernel-Collections'!
 !Set commentStamp!
 I represent an unordered set of objects without duplicates.
@@ -1862,7 +1862,7 @@ includes: anObject
 ! !
 
 Object subclass: #ProtoStream
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !ProtoStream commentStamp!
 I am the abstract base for different accessor for a sequence of objects. This sequence is referred to as my "contents".
@@ -1961,7 +1961,7 @@ on: aCollection
 ! !
 
 ProtoStream subclass: #Stream
-	instanceVariableNames: 'collection position streamSize'
+	slots: {#collection. #position. #streamSize}
 	package: 'Kernel-Collections'!
 !Stream commentStamp!
 I represent an accessor for a sequence of objects. This sequence is referred to as my "contents".
@@ -2086,7 +2086,7 @@ on: aCollection
 ! !
 
 Stream subclass: #StringStream
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !StringStream commentStamp!
 I am a Stream specific to `String` objects.!
@@ -2152,7 +2152,7 @@ tab
 ! !
 
 Object subclass: #Queue
-	instanceVariableNames: 'read readIndex write'
+	slots: {#read. #readIndex. #write}
 	package: 'Kernel-Collections'!
 !Queue commentStamp!
 I am a one-sided queue.
@@ -2207,7 +2207,7 @@ initialize
 ! !
 
 Object subclass: #RegularExpression
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Collections'!
 !RegularExpression commentStamp!
 I represent a regular expression object. My instances are JavaScript `RegExp` object.!

+ 5 - 5
lang/src/Kernel-Dag.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Dag'!
 Object subclass: #AbstractDagVisitor
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Dag'!
 !AbstractDagVisitor commentStamp!
 I am base class of `DagNode` visitor.
@@ -59,7 +59,7 @@ visitDagNodeVariantSimple: aNode
 ! !
 
 AbstractDagVisitor subclass: #PathDagVisitor
-	instanceVariableNames: 'path'
+	slots: {#path}
 	package: 'Kernel-Dag'!
 !PathDagVisitor commentStamp!
 I am base class of `DagNode` visitor.
@@ -102,7 +102,7 @@ visitDagNodeVariantRedux: aNode
 ! !
 
 Object subclass: #DagNode
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Dag'!
 !DagNode commentStamp!
 I am the abstract root class of any directed acyclic graph.
@@ -143,7 +143,7 @@ acceptDagVisitor: aVisitor
 ! !
 
 DagNode subclass: #DagParentNode
-	instanceVariableNames: 'nodes'
+	slots: {#nodes}
 	package: 'Kernel-Dag'!
 !DagParentNode commentStamp!
 I am `DagNode` that stores a collection of its children,
@@ -166,7 +166,7 @@ dagChildren: aCollection
 ! !
 
 DagNode subclass: #DagSink
-	instanceVariableNames: 'nodes'
+	slots: {#nodes}
 	package: 'Kernel-Dag'!
 !DagSink commentStamp!
 I am `DagNode` with no direct successors.

+ 5 - 5
lang/src/Kernel-Exceptions.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Exceptions'!
 Object subclass: #Error
-	instanceVariableNames: 'message stack amberHandled context smalltalkError'
+	slots: {#message. #stack. #amberHandled. #context. #smalltalkError}
 	package: 'Kernel-Exceptions'!
 !Error commentStamp!
 From the ANSI standard:
@@ -130,7 +130,7 @@ signal: aString
 ! !
 
 Error subclass: #Halt
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Exceptions'!
 !Halt commentStamp!
 I am provided to support `Object>>#halt`.!
@@ -153,7 +153,7 @@ signalerContextFrom: aContext
 ! !
 
 Error subclass: #JavaScriptException
-	instanceVariableNames: 'exception'
+	slots: {#exception}
 	package: 'Kernel-Exceptions'!
 !JavaScriptException commentStamp!
 A JavaScriptException is thrown when a non-Smalltalk exception occurs while in the Smalltalk stack.
@@ -202,7 +202,7 @@ on: anException context: aMethodContext
 ! !
 
 Error subclass: #MessageNotUnderstood
-	instanceVariableNames: 'smalltalkMessage receiver'
+	slots: {#smalltalkMessage. #receiver}
 	package: 'Kernel-Exceptions'!
 !MessageNotUnderstood commentStamp!
 This exception is provided to support `Object>>doesNotUnderstand:`.!
@@ -230,7 +230,7 @@ receiver: anObject
 ! !
 
 Error subclass: #NonBooleanReceiver
-	instanceVariableNames: 'object'
+	slots: {#object}
 	package: 'Kernel-Exceptions'!
 !NonBooleanReceiver commentStamp!
 NonBooleanReceiver exceptions may be thrown when executing inlined methods such as `#ifTrue:` with a non boolean receiver.!

+ 13 - 13
lang/src/Kernel-Infrastructure.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Infrastructure'!
 Object subclass: #AmberBootstrapInitialization
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Infrastructure'!
 
 !AmberBootstrapInitialization class methodsFor: 'organization'!
@@ -26,7 +26,7 @@ run
 ! !
 
 ProtoObject subclass: #JSObjectProxy
-	instanceVariableNames: 'jsObject'
+	slots: {#jsObject}
 	package: 'Kernel-Infrastructure'!
 !JSObjectProxy commentStamp!
 I handle sending messages to JavaScript objects, making  JavaScript object accessing from Amber fully transparent.
@@ -234,7 +234,7 @@ lookupProperty: aString ofProxy: aProxy
 ! !
 
 Object subclass: #Organizer
-	instanceVariableNames: 'elements'
+	slots: {#elements}
 	package: 'Kernel-Infrastructure'!
 !Organizer commentStamp!
 I represent categorization information. 
@@ -265,7 +265,7 @@ initialize
 ! !
 
 Organizer subclass: #ClassOrganizer
-	instanceVariableNames: 'traitOrBehavior'
+	slots: {#traitOrBehavior}
 	package: 'Kernel-Infrastructure'!
 !ClassOrganizer commentStamp!
 I am an organizer specific to classes. I hold method categorization information for classes.!
@@ -307,13 +307,13 @@ on: aClass
 ! !
 
 Organizer subclass: #PackageOrganizer
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Infrastructure'!
 !PackageOrganizer commentStamp!
 I am an organizer specific to packages. I hold classes categorization information.!
 
 Object subclass: #Package
-	instanceVariableNames: 'evalBlock basicTransport name transport imports dirty organization isReady'
+	slots: {#evalBlock. #basicTransport. #name. #transport. #imports. #dirty. #organization. #isReady}
 	package: 'Kernel-Infrastructure'!
 !Package commentStamp!
 I am similar to a "class category" typically found in other Smalltalks like Pharo or Squeak. Amber does not have class categories anymore, it had in the beginning but now each class in the system knows which package it belongs to.
@@ -591,7 +591,7 @@ validateImports: aCollection
 				self error: 'Keys must be identifiers' ]]]
 ! !
 
-Package class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
+Package class slots: {#defaultCommitPathJs. #defaultCommitPathSt}!
 
 !Package class methodsFor: 'accessing'!
 
@@ -663,7 +663,7 @@ sortedClasses: classes
 ! !
 
 Object subclass: #PackageStateObserver
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Infrastructure'!
 !PackageStateObserver commentStamp!
 My current instance listens for any changes in the system that might affect the state of a package (being dirty).!
@@ -713,7 +713,7 @@ onProtocolModification: anAnnouncement
 	anAnnouncement package ifNotNil: [ :package | package beDirty ]
 ! !
 
-PackageStateObserver class instanceVariableNames: 'current'!
+PackageStateObserver class slots: {#current}!
 
 !PackageStateObserver class methodsFor: 'accessing'!
 
@@ -728,14 +728,14 @@ initialize
 ! !
 
 Error subclass: #ParseError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Infrastructure'!
 !ParseError commentStamp!
 Instance of ParseError are signaled on any parsing error.
 See `Smalltalk >> #parse:`!
 
 Object subclass: #Setting
-	instanceVariableNames: 'key value defaultValue'
+	slots: {#key. #value. #defaultValue}
 	package: 'Kernel-Infrastructure'!
 !Setting commentStamp!
 I represent a setting **stored** at `Smalltalk settings`. 
@@ -796,7 +796,7 @@ new
 ! !
 
 Object subclass: #SmalltalkImage
-	instanceVariableNames: 'globalJsVariables packageDictionary'
+	slots: {#globalJsVariables. #packageDictionary}
 	package: 'Kernel-Infrastructure'!
 !SmalltalkImage commentStamp!
 I represent the Smalltalk system, wrapping
@@ -1104,7 +1104,7 @@ isSmalltalkObject: anObject
 	<inlineJS: 'return anObject.a$cls !!= null'>
 ! !
 
-SmalltalkImage class instanceVariableNames: 'current'!
+SmalltalkImage class slots: {#current}!
 
 !SmalltalkImage class methodsFor: 'initialization'!
 

+ 9 - 9
lang/src/Kernel-Methods.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Methods'!
 Object subclass: #BlockClosure
-	instanceVariableNames: 'prototype length'
+	slots: {#prototype. #length}
 	package: 'Kernel-Methods'!
 !BlockClosure commentStamp!
 I represent a lexical closure.
@@ -201,7 +201,7 @@ valueWithTimeout: aNumber
 ! !
 
 Object subclass: #CompiledMethod
-	instanceVariableNames: 'args fn messageSends owner protocol referencedClasses selector source'
+	slots: {#args. #fn. #messageSends. #owner. #protocol. #referencedClasses. #selector. #source}
 	package: 'Kernel-Methods'!
 !CompiledMethod commentStamp!
 I represent a class method of the system. I hold the source and compiled code of a class method.
@@ -337,7 +337,7 @@ isOverride
 ! !
 
 Object subclass: #ForkPool
-	instanceVariableNames: 'poolSize maxPoolSize queue worker'
+	slots: {#poolSize. #maxPoolSize. #queue. #worker}
 	package: 'Kernel-Methods'!
 !ForkPool commentStamp!
 I am responsible for handling forked blocks.
@@ -400,7 +400,7 @@ addWorker
 	poolSize := poolSize + 1
 ! !
 
-ForkPool class instanceVariableNames: 'default'!
+ForkPool class slots: {#default}!
 
 !ForkPool class methodsFor: 'accessing'!
 
@@ -417,7 +417,7 @@ resetDefault
 ! !
 
 Object subclass: #Message
-	instanceVariableNames: 'selector arguments'
+	slots: {#selector. #arguments}
 	package: 'Kernel-Methods'!
 !Message commentStamp!
 In general, the system does not use instances of me for efficiency reasons.
@@ -483,7 +483,7 @@ selector: aString arguments: anArray
 ! !
 
 Object subclass: #MessageSend
-	instanceVariableNames: 'receiver message'
+	slots: {#receiver. #message}
 	package: 'Kernel-Methods'!
 !MessageSend commentStamp!
 I encapsulate message sends to objects. Arguments can be either predefined or supplied when the message send is performed. 
@@ -567,7 +567,7 @@ printOn: aStream
 ! !
 
 Object subclass: #MethodContext
-	instanceVariableNames: 'receiver evaluatedSelector homeContext index locals outerContext selector sendIdx supercall'
+	slots: {#receiver. #evaluatedSelector. #homeContext. #index. #locals. #outerContext. #selector. #sendIdx. #supercall}
 	package: 'Kernel-Methods'!
 !MethodContext commentStamp!
 I hold all the dynamic state associated with the execution of either a method activation resulting from a message send. I am used to build the call stack while debugging.
@@ -626,7 +626,7 @@ stubToAtMost: anInteger
 ! !
 
 Object subclass: #NativeFunction
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Methods'!
 !NativeFunction commentStamp!
 I am a wrapper around native functions, such as `WebSocket`.
@@ -920,7 +920,7 @@ isBlockContext
 ! !
 
 Object subclass: #Timeout
-	instanceVariableNames: 'rawTimeout'
+	slots: {#rawTimeout}
 	package: 'Kernel-Methods'!
 !Timeout commentStamp!
 I am wrapping the returns from `set{Timeout,Interval}`.

+ 9 - 9
lang/src/Kernel-Objects.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Objects'!
 nil subclass: #ProtoObject
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !ProtoObject commentStamp!
 I implement the basic behavior required for any object in Amber.
@@ -155,7 +155,7 @@ initialize
 ! !
 
 ProtoObject subclass: #Object
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !Object commentStamp!
 **I am the root of the Smalltalk class system**. With the exception of unual subclasses of `ProtoObject`, all other classes in the system are subclasses of me.
@@ -407,7 +407,7 @@ initialize
 ! !
 
 Object subclass: #Boolean
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !Boolean commentStamp!
 I define the protocol for logic testing operations and conditional control structures for the logical values (see the `controlling` protocol).
@@ -535,7 +535,7 @@ isImmutable
 ! !
 
 Object subclass: #Date
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !Date commentStamp!
 I am used to work with both dates and times. Therefore `Date today` and `Date now` are both valid in
@@ -742,7 +742,7 @@ today
 ! !
 
 Object subclass: #Number
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !Number commentStamp!
 I am the Amber representation for all numbers.
@@ -1145,7 +1145,7 @@ radiansPerDegree
 ! !
 
 Object subclass: #Point
-	instanceVariableNames: 'x y'
+	slots: {#x. #y}
 	package: 'Kernel-Objects'!
 !Point commentStamp!
 I represent an x-y pair of numbers usually designating a geometric coordinate.
@@ -1338,7 +1338,7 @@ x: aNumber y: anotherNumber
 ! !
 
 Object subclass: #Random
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !Random commentStamp!
 I an used to generate a random number and I am implemented as a trivial wrapper around javascript `Math.random()`.
@@ -1382,7 +1382,7 @@ next: anInteger
 ! !
 
 Object subclass: #Rectangle
-	instanceVariableNames: 'origin corner'
+	slots: {#origin. #corner}
 	package: 'Kernel-Objects'!
 !Rectangle commentStamp!
 I represent a Rectangle defined by my two corners.
@@ -1450,7 +1450,7 @@ point: anOrigin point: aCorner
 ! !
 
 Object subclass: #UndefinedObject
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Objects'!
 !UndefinedObject commentStamp!
 I describe the behavior of my sole instance, `nil`. `nil` represents a prior value for variables that have not been initialized, or for results which are meaningless.

+ 1 - 1
lang/src/Kernel-Promises.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Promises'!
 Object subclass: #Promise
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Promises'!
 
 !Promise class methodsFor: 'composites'!

+ 32 - 32
lang/src/Kernel-Tests.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Kernel-Tests'!
 TestCase subclass: #AnnouncementSubscriptionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !AnnouncementSubscriptionTest methodsFor: 'tests'!
@@ -34,7 +34,7 @@ testHandlesAnnouncement
 ! !
 
 TestCase subclass: #AnnouncerTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !AnnouncerTest methodsFor: 'tests'!
@@ -87,7 +87,7 @@ testOnDoOnce
 ! !
 
 TestCase subclass: #BlockClosureTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !BlockClosureTest methodsFor: 'fixture'!
@@ -219,7 +219,7 @@ testWhileTrue
 ! !
 
 TestCase subclass: #BooleanTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !BooleanTest methodsFor: 'tests'!
@@ -338,7 +338,7 @@ testNonBooleanError
 ! !
 
 TestCase subclass: #ClassBuilderTest
-	instanceVariableNames: 'builder theClass'
+	slots: {#builder. #theClass}
 	package: 'Kernel-Tests'!
 
 !ClassBuilderTest methodsFor: 'running'!
@@ -447,7 +447,7 @@ testSubclass
 ! !
 
 TestCase subclass: #ClassTest
-	instanceVariableNames: 'builder theClass'
+	slots: {#builder. #theClass}
 	package: 'Kernel-Tests'!
 
 !ClassTest methodsFor: 'running'!
@@ -545,7 +545,7 @@ testTrickySetJavaScriptConstructor
 ! !
 
 TestCase subclass: #CollectionTest
-	instanceVariableNames: 'sampleBlock'
+	slots: {#sampleBlock}
 	package: 'Kernel-Tests'!
 
 !CollectionTest methodsFor: 'convenience'!
@@ -840,7 +840,7 @@ isAbstract
 ! !
 
 CollectionTest subclass: #IndexableCollectionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !IndexableCollectionTest methodsFor: 'fixture'!
@@ -959,7 +959,7 @@ testWithIndexDo
 ! !
 
 IndexableCollectionTest subclass: #AssociativeCollectionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !AssociativeCollectionTest methodsFor: 'fixture'!
@@ -1079,7 +1079,7 @@ testValues
 ! !
 
 AssociativeCollectionTest subclass: #DictionaryTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !DictionaryTest methodsFor: 'fixture'!
@@ -1189,7 +1189,7 @@ collectionClass
 ! !
 
 AssociativeCollectionTest subclass: #HashedCollectionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !HashedCollectionTest methodsFor: 'fixture'!
@@ -1239,7 +1239,7 @@ collectionClass
 ! !
 
 IndexableCollectionTest subclass: #SequenceableCollectionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !SequenceableCollectionTest methodsFor: 'fixture'!
@@ -1360,7 +1360,7 @@ testThird
 ! !
 
 SequenceableCollectionTest subclass: #ArrayTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !ArrayTest methodsFor: 'fixture'!
@@ -1491,7 +1491,7 @@ collectionClass
 ! !
 
 SequenceableCollectionTest subclass: #StringTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !StringTest methodsFor: 'fixture'!
@@ -1720,7 +1720,7 @@ collectionClass
 ! !
 
 CollectionTest subclass: #SetTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !SetTest methodsFor: 'fixture'!
@@ -1871,7 +1871,7 @@ collectionClass
 ! !
 
 TestCase subclass: #ConsoleTranscriptTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !ConsoleTranscriptTest methodsFor: 'tests'!
@@ -1888,7 +1888,7 @@ Transcript register: originalTranscript.
 ! !
 
 TestCase subclass: #DateTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !DateTest methodsFor: 'tests'!
@@ -1920,7 +1920,7 @@ testIdentity
 ! !
 
 TestCase subclass: #JSObjectProxyTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !JSObjectProxyTest methodsFor: 'accessing'!
@@ -2073,7 +2073,7 @@ testYourself
 ! !
 
 TestCase subclass: #JavaScriptExceptionTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !JavaScriptExceptionTest methodsFor: 'helpers'!
@@ -2096,7 +2096,7 @@ testRaisingException
 ! !
 
 TestCase subclass: #MessageSendTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !MessageSendTest methodsFor: 'tests'!
@@ -2126,7 +2126,7 @@ testValueWithArguments
 ! !
 
 TestCase subclass: #MethodInheritanceTest
-	instanceVariableNames: 'receiverTop receiverMiddle receiverBottom method performBlock'
+	slots: {#receiverTop. #receiverMiddle. #receiverBottom. #method. #performBlock}
 	package: 'Kernel-Tests'!
 
 !MethodInheritanceTest methodsFor: 'accessing'!
@@ -2266,7 +2266,7 @@ testReturns1
 ! !
 
 TestCase subclass: #NumberTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !NumberTest methodsFor: 'tests'!
@@ -2569,7 +2569,7 @@ testTruncated
 ! !
 
 Object subclass: #ObjectMock
-	instanceVariableNames: 'foo bar'
+	slots: {#foo. #bar}
 	package: 'Kernel-Tests'!
 !ObjectMock commentStamp!
 ObjectMock is there only to perform tests on classes.!
@@ -2585,7 +2585,7 @@ foo: anObject
 ! !
 
 TestCase subclass: #ObjectTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !ObjectTest methodsFor: 'tests'!
@@ -2670,7 +2670,7 @@ testYourself
 ! !
 
 TestCase subclass: #PointTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !PointTest methodsFor: 'tests'!
@@ -2756,7 +2756,7 @@ testTranslateBy
 ! !
 
 TestCase subclass: #QueueTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !QueueTest methodsFor: 'tests'!
@@ -2783,7 +2783,7 @@ testQueueNext
 ! !
 
 TestCase subclass: #RandomTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !RandomTest methodsFor: 'tests'!
@@ -2819,7 +2819,7 @@ textNext
 ! !
 
 TestCase subclass: #RectangleTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !RectangleTest methodsFor: 'tests'!
@@ -2846,7 +2846,7 @@ testOriginExtent
 ! !
 
 TestCase subclass: #StreamTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !StreamTest methodsFor: 'accessing'!
@@ -2975,7 +2975,7 @@ isAbstract
 ! !
 
 StreamTest subclass: #ArrayStreamTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !ArrayStreamTest methodsFor: 'accessing'!
@@ -2991,7 +2991,7 @@ collectionClass
 ! !
 
 StreamTest subclass: #StringStreamTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !StringStreamTest methodsFor: 'accessing'!
@@ -3007,7 +3007,7 @@ collectionClass
 ! !
 
 TestCase subclass: #UndefinedTest
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Kernel-Tests'!
 
 !UndefinedTest methodsFor: 'tests'!

+ 2 - 2
lang/src/Platform-Browser.st

@@ -1,7 +1,7 @@
 Smalltalk createPackage: 'Platform-Browser'!
 (Smalltalk packageAt: 'Platform-Browser' ifAbsent: [ self error: 'Package not created: Platform-Browser' ]) imports: {'amber/core/Platform-Services'}!
 Object subclass: #BrowserPlatform
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Browser'!
 !BrowserPlatform commentStamp!
 I am `Platform` service implementation for browser.!
@@ -29,7 +29,7 @@ isFeasible
 ! !
 
 Object subclass: #BrowserTerminal
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Browser'!
 !BrowserTerminal commentStamp!
 I am `Terminal` service implementation for browser.!

+ 1 - 1
lang/src/Platform-DOM-Tests.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Platform-DOM-Tests'!
 TestCase subclass: #PlatformDomTest
-	instanceVariableNames: 'fixtureDiv'
+	slots: {#fixtureDiv}
 	package: 'Platform-DOM-Tests'!
 
 !PlatformDomTest methodsFor: 'testing'!

+ 1 - 1
lang/src/Platform-DOM.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Platform-DOM'!
 Object subclass: #PlatformDom
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-DOM'!
 
 !PlatformDom class methodsFor: 'converting'!

+ 7 - 19
lang/src/Platform-ImportExport.js

@@ -279,14 +279,10 @@ $recv(aStream)._tab();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["tab"]=1;
 //>>excludeEnd("ctx");
-$recv(aStream)._write_("instanceVariableNames: ");
+$recv(aStream)._write_(["slots: {",". "._join_($recv($recv(aClass)._instanceVariableNames())._collect_("symbolPrintString")),"}"]);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["write:"]=2;
 //>>excludeEnd("ctx");
-$recv(aStream)._print_(" "._join_($recv(aClass)._instanceVariableNames()));
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["print:"]=2;
-//>>excludeEnd("ctx");
 $recv(aStream)._lf();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["lf"]=2;
@@ -298,7 +294,7 @@ $ctx1.sendIdx["write:"]=3;
 //>>excludeEnd("ctx");
 $recv(aStream)._print_($recv(aClass)._category());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["print:"]=3;
+$ctx1.sendIdx["print:"]=2;
 //>>excludeEnd("ctx");
 $recv(aStream)._write_("!");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -347,10 +343,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aClass", "aStream"],
-source: "exportDefinitionOf: aClass on: aStream\x0a\x09\x22Chunk format.\x22\x0a\x0a\x09aStream\x0a\x09\x09print: aClass superclass;\x0a\x09\x09write: ' subclass: ';\x0a\x09\x09printSymbol: aClass name;\x0a\x09\x09lf.\x0a\x09\x22aClass traitComposition\x0a\x09\x09ifNotEmpty: [ aStream tab; write: {'uses: '. aClass traitCompositionDefinition}; lf ].\x22\x0a\x09aStream\x0a\x09\x09tab;\x0a\x09\x09write: 'instanceVariableNames: ';\x0a\x09\x09print: (' ' join: aClass instanceVariableNames);\x0a\x09\x09lf;\x0a\x09\x09tab;\x0a\x09\x09write: 'package: ';\x0a\x09\x09print: aClass category;\x0a\x09\x09write: '!';\x0a\x09\x09lf.\x0a\x09aClass comment ifNotEmpty: [ aStream\x0a\x09\x09write: '!'; print: aClass; write: ' commentStamp!'; lf;\x0a\x09\x09write: { self chunkEscape: aClass comment. '!' }; lf ].\x0a\x09aStream lf",
+source: "exportDefinitionOf: aClass on: aStream\x0a\x09\x22Chunk format.\x22\x0a\x0a\x09aStream\x0a\x09\x09print: aClass superclass;\x0a\x09\x09write: ' subclass: ';\x0a\x09\x09printSymbol: aClass name;\x0a\x09\x09lf.\x0a\x09\x22aClass traitComposition\x0a\x09\x09ifNotEmpty: [ aStream tab; write: {'uses: '. aClass traitCompositionDefinition}; lf ].\x22\x0a\x09aStream\x0a\x09\x09tab;\x0a\x09\x09write: {'slots: {'. ('. ' join: (aClass instanceVariableNames collect: #symbolPrintString)). '}'};\x0a\x09\x09lf;\x0a\x09\x09tab;\x0a\x09\x09write: 'package: ';\x0a\x09\x09print: aClass category;\x0a\x09\x09write: '!';\x0a\x09\x09lf.\x0a\x09aClass comment ifNotEmpty: [ aStream\x0a\x09\x09write: '!'; print: aClass; write: ' commentStamp!'; lf;\x0a\x09\x09write: { self chunkEscape: aClass comment. '!' }; lf ].\x0a\x09aStream lf",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["print:", "superclass", "write:", "printSymbol:", "name", "lf", "tab", "join:", "instanceVariableNames", "category", "ifNotEmpty:", "comment", "chunkEscape:"]
+messageSends: ["print:", "superclass", "write:", "printSymbol:", "name", "lf", "tab", "join:", "collect:", "instanceVariableNames", "category", "ifNotEmpty:", "comment", "chunkEscape:"]
 }),
 $globals.ChunkExporter);
 
@@ -374,16 +370,8 @@ classTraitComposition=$recv($recv(aClass)._class())._traitComposition();
 $2=$recv(classIvars)._notEmpty();
 if($core.assert($2)){
 $recv(aStream)._print_($recv(aClass)._theMetaClass());
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["print:"]=1;
-//>>excludeEnd("ctx");
 $recv(aStream)._space();
-$recv(aStream)._write_("instanceVariableNames: ");
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["write:"]=1;
-//>>excludeEnd("ctx");
-$recv(aStream)._print_(" "._join_(classIvars));
-$recv(aStream)._write_("!");
+$recv(aStream)._write_(["slots: {",". "._join_($recv(classIvars)._collect_("symbolPrintString")),"}!"]);
 $recv(aStream)._lf();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["lf"]=1;
@@ -397,10 +385,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aClass", "aStream"],
-source: "exportMetaDefinitionOf: aClass on: aStream\x0a\x0a\x09| classIvars classTraitComposition |\x0a\x09classIvars := aClass class instanceVariableNames.\x0a\x09classTraitComposition := aClass class traitComposition.\x0a\x0a\x09(classIvars notEmpty \x22or: [classTraitComposition notEmpty]\x22) ifTrue: [\x0a\x09\x09aStream\x0a\x09\x09\x09print: aClass theMetaClass.\x0a\x09\x09aStream space. \x22classTraitComposition\x0a\x09\x09\x09ifEmpty: [ aStream space ]\x0a\x09\x09\x09ifNotEmpty: [ aStream lf; tab; write: {'uses: '. aClass class traitCompositionDefinition}; lf; tab ].\x22\x0a\x09\x09aStream\x0a\x09\x09\x09write: 'instanceVariableNames: ';\x0a\x09\x09\x09print: (' ' join: classIvars);\x0a\x09\x09\x09write: '!'; lf; lf ]",
+source: "exportMetaDefinitionOf: aClass on: aStream\x0a\x0a\x09| classIvars classTraitComposition |\x0a\x09classIvars := aClass class instanceVariableNames.\x0a\x09classTraitComposition := aClass class traitComposition.\x0a\x0a\x09(classIvars notEmpty \x22or: [classTraitComposition notEmpty]\x22) ifTrue: [\x0a\x09\x09aStream\x0a\x09\x09\x09print: aClass theMetaClass.\x0a\x09\x09aStream space. \x22classTraitComposition\x0a\x09\x09\x09ifEmpty: [ aStream space ]\x0a\x09\x09\x09ifNotEmpty: [ aStream lf; tab; write: {'uses: '. aClass class traitCompositionDefinition}; lf; tab ].\x22\x0a\x09\x09aStream\x0a\x09\x09\x09write: {'slots: {'. ('. ' join: (classIvars collect: #symbolPrintString)). '}!'}; lf; lf ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["instanceVariableNames", "class", "traitComposition", "ifTrue:", "notEmpty", "print:", "theMetaClass", "space", "write:", "join:", "lf"]
+messageSends: ["instanceVariableNames", "class", "traitComposition", "ifTrue:", "notEmpty", "print:", "theMetaClass", "space", "write:", "join:", "collect:", "lf"]
 }),
 $globals.ChunkExporter);
 

+ 17 - 20
lang/src/Platform-ImportExport.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Platform-ImportExport'!
 Object subclass: #AbstractExporter
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !AbstractExporter commentStamp!
 I am an abstract exporter for Amber source code.
@@ -49,7 +49,7 @@ exportPackage: aPackage on: aStream
 ! !
 
 AbstractExporter subclass: #ChunkExporter
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !ChunkExporter commentStamp!
 I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.
@@ -142,8 +142,7 @@ exportDefinitionOf: aClass on: aStream
 		ifNotEmpty: [ aStream tab; write: {'uses: '. aClass traitCompositionDefinition}; lf ]."
 	aStream
 		tab;
-		write: 'instanceVariableNames: ';
-		print: (' ' join: aClass instanceVariableNames);
+		write: {'slots: {'. ('. ' join: (aClass instanceVariableNames collect: #symbolPrintString)). '}'};
 		lf;
 		tab;
 		write: 'package: ';
@@ -169,9 +168,7 @@ exportMetaDefinitionOf: aClass on: aStream
 			ifEmpty: [ aStream space ]
 			ifNotEmpty: [ aStream lf; tab; write: {'uses: '. aClass class traitCompositionDefinition}; lf; tab ]."
 		aStream
-			write: 'instanceVariableNames: ';
-			print: (' ' join: classIvars);
-			write: '!!'; lf; lf ]
+			write: {'slots: {'. ('. ' join: (classIvars collect: #symbolPrintString)). '}!!'}; lf; lf ]
 !
 
 exportMethod: aMethod on: aStream
@@ -273,7 +270,7 @@ exportTraitDefinitionOf: aClass on: aStream
 ! !
 
 AbstractExporter subclass: #Exporter
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !Exporter commentStamp!
 I am responsible for outputting Amber code into a JavaScript string.
@@ -443,7 +440,7 @@ exportTraitDefinitionOf: aClass on: aStream
 ! !
 
 Exporter subclass: #AmdExporter
-	instanceVariableNames: 'namespace'
+	slots: {#namespace}
 	package: 'Platform-ImportExport'!
 !AmdExporter commentStamp!
 I am used to export Packages in an AMD (Asynchronous Module Definition) JavaScript format.!
@@ -527,7 +524,7 @@ importsForOutput: aPackage
 ! !
 
 Object subclass: #ChunkParser
-	instanceVariableNames: 'stream last'
+	slots: {#stream. #last}
 	package: 'Platform-ImportExport'!
 !ChunkParser commentStamp!
 I am responsible for parsing aStream contents in the chunk format.
@@ -580,7 +577,7 @@ on: aStream
 ! !
 
 Object subclass: #ClassCommentReader
-	instanceVariableNames: 'class'
+	slots: {#class}
 	package: 'Platform-ImportExport'!
 !ClassCommentReader commentStamp!
 I provide a mechanism for retrieving class comments stored on a file.
@@ -615,7 +612,7 @@ setComment: aString
 ! !
 
 Object subclass: #ClassProtocolReader
-	instanceVariableNames: 'class category'
+	slots: {#class. #category}
 	package: 'Platform-ImportExport'!
 !ClassProtocolReader commentStamp!
 I provide a mechanism for retrieving class descriptions stored on a file in the Smalltalk chunk format.!
@@ -649,7 +646,7 @@ compileMethod: aString
 ! !
 
 Object subclass: #ExportMethodProtocol
-	instanceVariableNames: 'name theClass'
+	slots: {#name. #theClass}
 	package: 'Platform-ImportExport'!
 !ExportMethodProtocol commentStamp!
 I am an abstraction for a method protocol in a class / metaclass.
@@ -695,7 +692,7 @@ name: aString theClass: aClass
 ! !
 
 Object subclass: #Importer
-	instanceVariableNames: 'lastSection lastChunk'
+	slots: {#lastSection. #lastChunk}
 	package: 'Platform-ImportExport'!
 !Importer commentStamp!
 I can import Amber code from a string in the chunk format.
@@ -739,13 +736,13 @@ import: aStream
 ! !
 
 Error subclass: #PackageCommitError
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !PackageCommitError commentStamp!
 I get signaled when an attempt to commit a package has failed.!
 
 Object subclass: #PackageHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !PackageHandler commentStamp!
 I am responsible for handling package loading and committing.
@@ -863,7 +860,7 @@ ajaxPutAt: aURL data: aString onSuccess: aBlock onError: anotherBlock
 ! !
 
 PackageHandler subclass: #AmdPackageHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-ImportExport'!
 !AmdPackageHandler commentStamp!
 I am responsible for handling package loading and committing.
@@ -942,7 +939,7 @@ defaultNamespace: aString
 ! !
 
 Object subclass: #PackageTransport
-	instanceVariableNames: 'package'
+	slots: {#package}
 	package: 'Platform-ImportExport'!
 !PackageTransport commentStamp!
 I represent the transport mechanism used to commit a package.
@@ -1017,7 +1014,7 @@ load
 		then: [ Smalltalk postLoad ]
 ! !
 
-PackageTransport class instanceVariableNames: 'registry'!
+PackageTransport class slots: {#registry}!
 
 !PackageTransport class methodsFor: 'accessing'!
 
@@ -1069,7 +1066,7 @@ register: aClass
 ! !
 
 PackageTransport subclass: #AmdPackageTransport
-	instanceVariableNames: 'namespace'
+	slots: {#namespace}
 	package: 'Platform-ImportExport'!
 !AmdPackageTransport commentStamp!
 I am the default transport for committing packages.

+ 1 - 1
lang/src/Platform-Node.st

@@ -1,7 +1,7 @@
 Smalltalk createPackage: 'Platform-Node'!
 (Smalltalk packageAt: 'Platform-Node' ifAbsent: [ self error: 'Package not created: Platform-Node' ]) imports: {'amber/core/Platform-Services'}!
 Object subclass: #NodePlatform
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Node'!
 !NodePlatform commentStamp!
 I am `Platform` service implementation for node-like environment.!

+ 15 - 15
lang/src/Platform-Services.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Platform-Services'!
 Object subclass: #ConsoleErrorHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !ConsoleErrorHandler commentStamp!
 I am manage Smalltalk errors, displaying the stack in the console.!
@@ -34,7 +34,7 @@ logErrorContext: aContext
 			self logContext: aContext home ]]
 ! !
 
-ConsoleErrorHandler class instanceVariableNames: 'current'!
+ConsoleErrorHandler class slots: {#current}!
 
 !ConsoleErrorHandler class methodsFor: 'initialization'!
 
@@ -43,7 +43,7 @@ initialize
 ! !
 
 Object subclass: #ConsoleTranscript
-	instanceVariableNames: 'textarea'
+	slots: {#textarea}
 	package: 'Platform-Services'!
 !ConsoleTranscript commentStamp!
 I am a specific transcript emitting to the JavaScript console.
@@ -77,7 +77,7 @@ initialize
 ! !
 
 Object subclass: #Environment
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Environment commentStamp!
 I provide an unified entry point to manipulate Amber packages, classes and methods.
@@ -292,7 +292,7 @@ registerTranscript: aTranscript
 ! !
 
 Object subclass: #NullProgressHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !NullProgressHandler commentStamp!
 I am the default progress handler. I do not display any progress, and simply iterate over the collection.!
@@ -303,7 +303,7 @@ do: aBlock on: aCollection displaying: aString
 	aCollection do: aBlock
 ! !
 
-NullProgressHandler class instanceVariableNames: 'current'!
+NullProgressHandler class slots: {#current}!
 
 !NullProgressHandler class methodsFor: 'initialization'!
 
@@ -312,7 +312,7 @@ initialize
 ! !
 
 Object subclass: #Service
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Service commentStamp!
 I implement the basic behavior for class registration to a service.
@@ -323,7 +323,7 @@ See the `Transcript` class for a concrete service.
 
 Use class-side methods `#register:` and `#registerIfNone:` to register classes to a specific service.!
 
-Service class instanceVariableNames: 'current'!
+Service class slots: {#current}!
 
 !Service class methodsFor: 'accessing'!
 
@@ -348,7 +348,7 @@ registerIfNone: anObject
 ! !
 
 Service subclass: #ErrorHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !ErrorHandler commentStamp!
 I am the service used to handle Smalltalk errors.
@@ -375,7 +375,7 @@ handleUnhandledError: anError
 ! !
 
 Service subclass: #Finder
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Finder commentStamp!
 I am the service responsible for finding classes/methods.
@@ -400,7 +400,7 @@ findString: aString
 ! !
 
 Service subclass: #Inspector
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Inspector commentStamp!
 I am the service responsible for inspecting objects.
@@ -414,7 +414,7 @@ inspect: anObject
 ! !
 
 Service subclass: #Platform
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Platform commentStamp!
 I am bridge to JS environment.
@@ -444,7 +444,7 @@ includesGlobal: aString
 ! !
 
 Service subclass: #ProgressHandler
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !ProgressHandler commentStamp!
 I am used to manage progress in collection iterations, see `SequenceableCollection >> #do:displayingProgress:`.
@@ -460,7 +460,7 @@ do: aBlock on: aCollection displaying: aString
 ! !
 
 Service subclass: #Terminal
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Terminal commentStamp!
 I am UI interface service.
@@ -490,7 +490,7 @@ prompt: aString default: defaultString
 ! !
 
 Service subclass: #Transcript
-	instanceVariableNames: ''
+	slots: {}
 	package: 'Platform-Services'!
 !Transcript commentStamp!
 I am a facade for Transcript actions.

+ 2 - 2
lang/src/SUnit-Tests.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'SUnit-Tests'!
 TestCase subclass: #ExampleSetTest
-	instanceVariableNames: 'empty full'
+	slots: {#empty. #full}
 	package: 'SUnit-Tests'!
 !ExampleSetTest commentStamp!
 ExampleSetTest is taken from Pharo 1.4.
@@ -54,7 +54,7 @@ testRemove
 ! !
 
 TestCase subclass: #SUnitAsyncTest
-	instanceVariableNames: 'flag'
+	slots: {#flag}
 	package: 'SUnit-Tests'!
 
 !SUnitAsyncTest methodsFor: 'helpers'!

+ 7 - 7
lang/src/SUnit.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'SUnit'!
 Object subclass: #ResultAnnouncement
-	instanceVariableNames: 'result'
+	slots: {#result}
 	package: 'SUnit'!
 !ResultAnnouncement commentStamp!
 I get signaled when a `TestCase` has been run.
@@ -18,7 +18,7 @@ result: aTestResult
 ! !
 
 Object subclass: #TestCase
-	instanceVariableNames: 'testSelector asyncTimeout context'
+	slots: {#testSelector. #asyncTimeout. #context}
 	package: 'SUnit'!
 !TestCase commentStamp!
 I am an implementation of the command pattern to run a test.
@@ -197,7 +197,7 @@ shouldInheritSelectors
 ! !
 
 Object subclass: #TestContext
-	instanceVariableNames: 'testCase'
+	slots: {#testCase}
 	package: 'SUnit'!
 !TestContext commentStamp!
 I govern running a particular test case.
@@ -245,7 +245,7 @@ testCase: aTestCase
 ! !
 
 TestContext subclass: #ReportingTestContext
-	instanceVariableNames: 'finished result'
+	slots: {#finished. #result}
 	package: 'SUnit'!
 !ReportingTestContext commentStamp!
 I add `TestResult` reporting to `TestContext`.
@@ -295,7 +295,7 @@ testCase: aTestCase result: aTestResult finished: aBlock
 ! !
 
 Error subclass: #TestFailure
-	instanceVariableNames: ''
+	slots: {}
 	package: 'SUnit'!
 !TestFailure commentStamp!
 I am raised when the boolean parameter of an #`assert:` or `#deny:` call is the opposite of what the assertion claims.
@@ -305,7 +305,7 @@ A failure is an event whose possibiity is explicitly anticipated and checked for
 whereas an error is an unanticipated problem like a division by 0 or an index out of bounds.!
 
 Object subclass: #TestResult
-	instanceVariableNames: 'timestamp runs errors failures total'
+	slots: {#timestamp. #runs. #errors. #failures. #total}
 	package: 'SUnit'!
 !TestResult commentStamp!
 I implement the collecting parameter pattern for running a bunch of tests.
@@ -385,7 +385,7 @@ runCase: aTestCase
 ! !
 
 Object subclass: #TestSuiteRunner
-	instanceVariableNames: 'suite result announcer runNextTest'
+	slots: {#suite. #result. #announcer. #runNextTest}
 	package: 'SUnit'!
 !TestSuiteRunner commentStamp!
 I am responsible for running a collection (`suite`) of tests.

+ 1 - 1
sdk/lib/NodeTestRunner.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'NodeTestRunner'!
 Object subclass: #NodeTestRunner
-	instanceVariableNames: ''
+	slots: {}
 	package: 'NodeTestRunner'!
 
 !NodeTestRunner class methodsFor: 'not yet classified'!