IMD 1.17: 19/01/2010 20:43:15 sc source 1 of 1  >;&ZUniFLEX Backup | |jTektronix 44042  !"#$%&'()*+,-./01234('&%$#"! g, g >: removeMultipleInheritance.st. _ڌ OZ^l ʀʈʃ-z \Sx,Cz4 'From Tektronix Smalltalk-80 version TB2.2.1x4, of May 8, 1987 on 1 July 1987 at 10:16:41 am'! "Filing in this file will remove the support for Multiple Inheritance from the Smalltalk system and fix a couple of class creation bugs."! !Object methodsFor: 'error handling'! doesNotUnderstand: aMessage "No method was found to respond to the argument, aMessage. The default behavior is to create a Notifier containing the appropriate message and to allow the user to open a Debugger. Subclasses can override this message in order to modify this behavior." "3 zork." NotifierView openContext: thisContext label: 'Message not understood: ' , aMessage selector contents: thisContext shortStack. "Try the message again if the programmer decides to proceed." ^self perform: aMessage selector withArguments: aMessage arguments! ! Object removeSelector: #conflictingInheritanceError! Behavior comment: 'Behavior provides the minimum state necessary for compiling methods, and creating and running instances. Most objects are created as instances of the more fully supported subclass, Class, but Behavior is a good starting point for providing instance-specific behavior (as in Metaclass). Behavior also implements single inheritance (the ability for a class to inherit implementation and behavior from one other class). Behavior encapsulates the portion of a class description used by the interpreter, and as such should not be redefined. Instance Variables: format encoding the storage layout of instances. methodDict that associates message names with methods. subclasses of back-pointers to the class'' subclasses. superclass from which we inherit both implementation and behavior. Class Variables: PrototypeObsoleteDoesNotUnderstand used to mutate instances of an obsolete class to an instance of the class that replaced it. '! !Behavior methodsFor: 'initialize-release'! obsolete "Invalidate and recycle local messages. Remove the receiver from its superclass' subclass list." methodDict _ MethodDictionary new. superclass removeSubclass: self! ! !Behavior methodsFor: 'testing'! isBytes "Answer whether the receiver has 8-bit instance variables." ^format noMask: 8192! ! !Behavior methodsFor: 'printing'! printHierarchy "Answer a description containing the names and instance variable names of all of the subclasses and superclasses of the receiver." | aStream index | index _ 0. aStream _ WriteStream on: (String new: 16). self allSuperclasses reverseDo: [:aClass | aStream crtab: index. index _ index + 1. aStream nextPutAll: aClass name. aStream space. aStream print: aClass instVarNames]. aStream cr. self printSubclassesOn: aStream level: index. ^aStream contents! printOn: aStream "Print a representation of myself on the argument, aStream." aStream nextPutAll: 'a descendent of '. superclass printOn: aStream! ! !Behavior methodsFor: 'creating class hierarchy'! addSubclass: aSubclass "Make the argument, aSubclass, be one of the subclasses of the receiver." aSubclass superclass == self ifTrue: [subclasses == nil ifTrue: [subclasses _ Set with: aSubclass] ifFalse: [subclasses add: aSubclass]] ifFalse: [self error: aSubclass name , ' is not my subclass']! removeSubclass: aSubclass "If the argument, aSubclass, is one of the receiver's subclasses, remove it." (subclasses == nil or: [self isObsolete]) ifFalse: [subclasses remove: aSubclass ifAbsent: []. subclasses isEmpty ifTrue: [subclasses _ nil]]! ! !Behavior methodsFor: 'creating method dictionary'! addSelector: selector withMethod: compiledMethod "Add the message selector with the corresponding compiled method to the receiver's method dictionary." methodDict at: selector put: compiledMethod. self flushCache! removeSelector: selector "Assuming that the message selector is in the receiver's method dictionary, remove it. If the selector is not in the method dictionary, create an error notification." methodDict removeKey: selector.  self flushCache! ! !Behavior methodsFor: 'accessing class hierarchy'! allSubclasses "Answer an OrderedCollection of the receiver's subclasses and the receiver's ancestor's subclasses in breadth-first order, with the immediate subclasses first." | coll | coll _ OrderedCollection new. coll addAll: self subclasses. self subclasses do: [:eachSubclass | coll addAll: eachSubclass allSubclasses]. ^coll! allSuperclasses "Answer an OrderedCollection of the receiver's superclasses and the receiver's ancestor's superclasses, with the immediate superclasses first." | superclasses | superclass == nil ifTrue: [^OrderedCollection new]. superclasses _ superclass allSuperclasses. superclasses addFirst: superclass. ^superclasses! superclass "Answer the receiver's superclass." ^superclass! withAllSubclasses "Answer an OrderedCollection of subclasses including this class in breadth first order." | subs | subs _ self allSubclasses. subs addFirst: self. ^subs! withAllSuperclasses "Answer an OrderedCollection of superclasses including this class in breadth first order." | subs | subs _ self allSuperclasses. subs addFirst: self. ^subs! ! !Behavior methodsFor: 'accessing method dictionary'! allSelectors "Answer a set of all the message selectors that instances of the receiver can understand." "Point allSelectors." superclass == nil ifTrue: [^self selectors]. ^superclass allSelectors , self selectors! methodDescriptionAt: selector "Return a method description for the method for 'selector'." (methodDict includesKey: selector) ifTrue: [^MethodDescription whichClass: self selector: selector]. ^superclass methodDescriptionAt: selector! selectors "Answer a Set of all the message selectors specified in the receiver's method dictionary." "Point selectors." ^methodDict keys! sourceCodeAt: messageSelector "Answer the string corresponding to the source code for the argument." ^self sourceCodeForMethod: (methodDict at: messageSelector) at: messageSelector! sourceCodeForMethod: method at: messageSelector "Answer the string corresponding to the source code for the argument." | newSource index | Sensor leftShiftDown ifTrue: [newSource _ (self decompilerClass new decompile: messageSelector in: self method: method) decompileString] ifFalse: [newSource _ method getSource. newSource == nil ifTrue: [newSource _ (self decompilerClass new decompile: messageSelector in: self method: method) decompileString] ifFalse: [((newSource at: newSource size) isSeparator) ifTrue: [index _ newSource size. "tidy up for file out" [((newSource at: index) isSeparator) and: [index > 1]] whileTrue: [index _ index - 1]. newSource _ newSource copyFrom: 1 to: index]]]. ^newSource! ! !Behavior methodsFor: 'accessing instances and variables'! allClassVarNames "Answer a Set of the names of the receiver's and the receiver's ancestor's class variables." | superNames | superNames _ superclass == nil ifTrue: [Set new] ifFalse: [superclass allClassVarNames]. superNames addAll: self classVarNames. ^superNames! allInstVarNames "Answer an Array of the names of all of the receiver's instance variables, whether defined locally of inherited." | superNames | superNames _ superclass == nil ifTrue: [Array new] ifFalse: [superclass allInstVarNames]. ^superNames , self instVarNames! allSharedPools "Answer a Set of the pools, dictionaries, that the receiver and the receiver's ancestors share. Subclasses, such as class Class, override this message." | superPools | superPools _ superclass == nil ifTrue: [Set new] ifFalse: [superclass allSharedPools]. superPools addAll: self sharedPools. ^superPools! instVarNames "Answer an Array of the instance variable names. Behaviors must make up fake local instance variable names because Behaviors have instance variables for the purpose of compiling methods, but these are not named instance variables. " | mySize superSize | mySize _ self instSize. superSize _ superclass == nil ifTrue: [0] ifFalse: [superclass instSize]. mySize = superSize ifTrue: [^#()]. ^(superSize + 1 to: mySize) collect: [:i | 'inst' , i printString]! ! !Behavior methodsFor: 'testing class hierarchy'! inheritsFrom: aClass "Answer whether the argument, aClass, is on the receiver's superclass chain." | aSuperclass | aSuperclass _ superclass. [aSuperclass == nil] whileFalse: [aSuperclass == aClass ifTrue: [^true]. aSuperclass _ aSuperclass superclass]. ^false! ! !Behavior methodsFor: 'compiling'! compileAll "Compile all the methods in my method dictionary." ^self compileAllFrom: self! poolHas: varName ifTrue: assocBlock "Behaviors have no pools." ^false! recompile: selector "Recompile the method associated with the first argument, selector." ^self recompile: selector from: self! ! !Behavior methodsFor: 'private'! printSubclassesOn: aStream level: level "As part of the algorithm for printing a description of the receiver, print the subclass on the file stream, aStream, indenting level times." | subs | aStream crtab: level. aStream nextPutAll: self name. aStream space. aStream print: self instVarNames. subs _ self subclasses. self == Class ifTrue: [aStream crtab: level + 1. aStream nextPutAll: '... all the Metaclasses ...'. subs _ subs reject: [:sub | sub isMeta]]. "Print subclasses in alphabetical order" (subs asSortedCollection: [:x :y | x name < y name]) do: [:sub | sub printSubclassesOn: aStream level: level + 1]! ! Behavior removeSelector: #removeClass:selector:in:! Behavior removeSelector: #superMethodDescriptionAt:! Behavior removeSelector: #compoundSelectorsMatching:! Behavior removeSelector: #checkMethodFor:! Behavior removeSelector: #tryCopyingCodeFor:! Behavior removeSelector: #printSubclassesOn:callingSuperclass:level:! Behavior removeSelector: #subclassesForMutation! Behavior removeSelector: #compileBroadcastCodeFor:! Behavior removeSelector: #allDynamicSuperclasses! Behavior removeSelector: #removeSelectorUnchecked:! Behavior removeSelector: #hasMultipleSuperclasses! Behavior removeSelector: #allSuperclassesInto:! Behavior removeSelector: #removeFromInheritanceTable:! Behavior removeSelector: #addSelectorUnchecked:withMethod:! Behavior removeSelector: #updateInheritanceTables:! Behavior removeSelector: #checkChangeSelector:! Behavior removeSelector: #copyMethods! Behavior removeSelector: #insertClass:selector:in:! Behavior removeSelector: #compileUnchecked:! Behavior removeSelector: #dynamicSuperclass! Behavior removeSelector: #updateInheritanceTable:oldSelf:! Behavior removeSelector: #compileConflictCodeFor:! Behavior removeSelector: #checkSuperAddSelector:! Behavior removeSelector: #conflictCodeFor:! Behavior removeSelector: #releaseMethods! Behavior removeSelector: #superclasses! Behavior removeSelector: #accumulateInstVarNames:traversedClasses:! Behavior removeSelector: #removeFromInheritanceTables! Behavior removeSelector: #dynamicMethodDescriptionAt:! ClassDescription comment: 'ClassDescription is an abstract class which adds descriptive power to the implementation provided by Behavior. Specifically, it adds the ability to declare names for instance variables (Behavior supports non-indexed instance variables, but not names for them), the ability to group methods into categories (refered to as ''protocols''), the notion of a class name, the automatic maintenance of Change sets and the changes file, and the mechanism for filing out a class. Instance Variables: instanceVariables of the names of instance fields. organization providing the organization of messages into protocols. '! !ClassDescription methodsFor: 'testing'! isMeta "Answer true if the receiver is a metaclass." ^false! ! !ClassDescription methodsFor: 'printing'! definition "Answer a string that defines the receiver." | aStream name | aStream _ WriteStream on: (String new: 300). aStream nextPutAll: (superclass == nil ifTrue: ['nil'] ifFalse: [superclass name]). aStream nextPutAll: self kindOfSubclass. self name storeOn: aStream. aStream cr; tab; nextPutAll: 'instanceVariableNames: '. aStream store: self instanceVariablesString. aStream cr; tab; nextPutAll: 'classVariableNames: '. aStream store: self classVariablesString. aStream cr; tab; nextPutAll: 'poolDictionaries: '. aStream store: self sharedPoolsString. aStream cr; tab; nextPutAll: 'category: '. (name _ SystemOrganization categoryOfElement: self name) notNil ifTrue: [name asString storeOn: aStream] ifFalse: [' Tracer-Support' storeOn: aStream]. ^aStream contents! printOn: aStream "Print a textual representation of the receiver on the argument, aStream." aStream nextPutAll: self name! storeOn: aStream "Print a textual representation of the receiver on the argument, aStream, which will create an object equal (=) to the receiver when compiled. Classes and Metaclasses have global names." aStream nextPutAll: self name! superclassesString "Answer a string of my superclass names separated by spaces." ^superclass name! ! !ClassDescription methodsFor: 'organization'! organization "Answer the instance of ClassOrganizer that represents the organization of the messages of the receiver." organization==nil ifTrue: [organization _ ClassOrganizer new]. ^organization! ! !ClassDescription methodsFor: 'compiling'! compile: code notifying: requestor trailer: bytes ifFail: failBlock "Intercept this message in order to remember system changes." | methodNode selector | Cursor execute showWhile: [methodNode _ self compilerClass new compile: code in: self notifying: requestor ifFail: failBlock. selector _ methodNode selector. (methodDict includesKey: selector) ifTrue: [Smalltalk changes changeSelector: selector class: self] ifFalse: [Smalltalk changes addSelector: selector class: self]. self addSelector: selector withMethod: (methodNode generate: bytes)]. ^selector! ! !ClassDescription methodsFor: 'private'! errorCategoryName "Report that a category name has been used which was not a String." self error: 'Category name must be a String'! ! Class comment: 'My instances describe the representation and behavior of objects. I add more comprehensive programming support facilities to the basic attributes of Behavior and the descriptive facilities of ClassDescription. An example is accessing shared (pool) variables. [Subtle] The classes in the Smalltalk system are NOT instances of the class Class. They are instances of an object refered to as the metaclass. There is a one-to-one mapping between classes and metaclasses. Each metaclass is an instance of the class Metaclass (cf). However, because of the structure of the inheritance chain, all classes understand the protocol and have the implementation described by this class. See the book "Smalltalk-80: The Language and It''s Implementation", pp. 269-272, for a more detailed explanation. Instance Variables: classPool of variables common to all instances. Class variables may be accessed by the class and by instances of the class. name used as the name of the class for printing and global reference. sharedPools of Dictionaries containing other shared variables. A pool variable may be accessed by the class, instances of the class, and any other class which declares the pool. '! !Class methodsFor: 'initialize-release'! obsolete "Make the receiver be an obsolete class." ('AnObsolete*' match: name) ifFalse: [name _ 'AnObsolete' , name]. classPool _ Dictionary new. self class obsolete. super obsolete! ! !Class methodsFor: 'copying'! copy "Answer a copy of the receiver." | newClass | newClass _ self class copy new superclass: superclass methodDict: methodDict copy format: format name: name organization: organization copy instVarNames: instanceVariables copy classPool: classPool copy sharedPools: sharedPools. Class instSize to: self class instSize do: [:offset | newClass instVarAt: offset put: (self instVarAt: offset)]. ^newClass! ! !Class methodsFor: 'class name'! rename: aString "The new name of the receiver is the argument, aString." | newName | newName _ aString asSymbol. Smalltalk removeOrBrowse: newName. "Only returns if the name is no longer defined." Smalltalk renameClass: self as: newName. name _ newName. self comment: self comment. self class comment: self class comment! ! !Class methodsFor: 'instance variables'! addInstVarName: aString "Add the argument, aString, as one of the receiver's instance variables." superclass class name: self name inEnvironment: Smalltalk subclassOf: superclass instanceVariableNames: self instanceVariablesString , aString variable: self isVariable words: self isWords pointers: self isPointers classVariableNames: self classVariablesString poolDictionaries: self sharedPoolsString category: self category comment: nil changed: false! removeInstVarName: aString "Remove the argument, aString, as one of the receiver's instance variables." | newInstVarString | (self instVarNames includes: aString) ifFalse: [self error: aString , ' is not one of my instance variables']. newInstVarString _ ''. (self instVarNames copyWithout: aString) do: [:varName | newInstVarString _ newInstVarString , ' ' , varName]. superclass class name: self name inEnvironment: Smalltalk subclassOf: superclass instanceVariableNames: newInstVarString variable: self isVariable words: self isWords pointers: self isPointers classVariableNames: self classVariablesString poolDictionaries: self sharedPoolsString category: self category comment: nil changed: false! ! !Class methodsFor: 'class variables'! initialize "Typically used for the initialization of class variables and metaclass instance variables. Does nothing, but may be overridden in Metaclasses." ^self! ! !Class methodsFor: 'compiling'! compileAllFrom: otherClass "Compile all of the methods from the argument, otherClass." super compileAllFrom: otherClass. self class compileAllFrom: otherClass class! poolHas: varName ifTrue: assocBlock "Look up the first argument in the context of the receiver. If it is there, pass the association to assocBlock, and answer true, else answer false." | assoc pool | assoc _ self classPool associationAt: varName ifAbsent: []. assoc == nil ifFalse: [assocBlock value: assoc. ^true]. self sharedPools do: [:pool | assoc _ pool associationAt: varName ifAbsent: []. assoc == nil ifFalse: [assocBlock value: assoc. ^true]]. ^false! ! !Class methodsFor: 'fileIn-Out'! removeFromChanges "References to the receiver, a class, and its metaclass should no longer be included in the system ChangeSet." Smalltalk changes removeClassChanges: self! ! Class removeSelector: #hasMultipleSuperclasses! Class removeSelector: #allSharedPools! Class removeSelector: #allClassVarNames! Class removeSelector: #subclass:otherSupers:instanceVariableNames:classVariableNames:category:! Behavior class removeSelector: #init! Class class removeSelector: #named:superclasses:instanceVariableNames:classVariableNames:category:! Class class removeSelector: #getSuperclasses:! Metaclass comment: 'Metaclasses add instance-specific behavior to various classes in the system. This typically includes messages for initializing class variables and instance creation messages particular to that class. There is only one instance of a metaclass, namely the class which is being described. A metaclass shares the class variables of its instance. [Subtle] In general, the superclass hierarchy for metaclasses parallels that for classes. Thus, Integer superclass == Number, and Integer class superclass == Number class. However there is a singularity at Object. Here the class hierarchy terminates, but the metaclass hierarchy must wrap around to Class, since ALL metaclasses are subclasses of Class. Thus, Object superclass == nil, and Object class superclass == Class. Instance Variables: thisClass which is the unique instance of me. '! !Metaclass reorganize! ('initialize-release' instanceVariableNames: newNamed: obsolete obsoleteForMutationTo: subclassOf: superclass:) ('accessing' name soleInstance) ('testing' isMeta isObsolete) ('copying' copy copyForValidation) ('instance creation' new) ('instance variables' addInstVarName: removeInstVarName:) ('class variables' addClassVarName: classPool) ('class hierarchy' name:inEnvironment:subclassOf:instanceVariableNames:variable:words:pointers:classVariableNames:poolDictionaries:category:comment:changed: subclasses) ('compiling' scopeHas:ifTrue:) ('printing' definition storeDefinitionOn:auxTable:) ('fileIn-Out' fileOutOn:moveSource:toFile: nonTrivial) ! !Metaclass methodsFor: 'initialize-release'! newNamed: aSymbol "Answer a new instance of me whose name is the argument, aSymbol." ^(Metaclass subclassOf: self) new superclass: Object methodDict: MethodDictionary new format: -8192 name: aSymbol organization: ClassOrganizer new instVarNames: nil classPool: nil sharedPools: nil! ! !Metaclass methodsFor: 'testing'! isMeta "Answer true if the receiver is a metaclass." ^true! ! !Metaclass methodsFor: 'copying'! copy "Make a copy of the receiver without a list of subclasses. Share the reference to the sole instance." | copy soleInstance | soleInstance _ thisClass. thisClass _ nil. copy _ super copy. thisClass _ soleInstance. ^copy! ! !Metaclass methodsFor: 'class variables'! addClassVarName: aString ^thisClass addClassVarName: aString! ! !Metaclass methodsFor: 'class hierarchy'! isValidName: newName "Answer true if the argument, newName, is a valid name for a subclass of the receiver's sole instance. Answer false and notify the user of the problem otherwise." | superNames | newName first isUppercase ifFalse: [self notify: 'Class names must be capitalized.'. ^false]. superNames _ thisClass withAllSuperclasses collect: [:aClass | aClass name]. (superNames includes: newName) ifTrue: [self notify: 'Attempt to circularly define ' , newName , '.'. ^false]. ^true! name: newName inEnvironment: environ subclassOf: sup instanceVariableNames: instVarString variable: v words: w pointers: p classVariableNames: classVarString poolDictionaries: poolString category: categoryName comment: commentString changed: changed "Create a new metaclass from the information provided in the arguments. Create an error if the name does not begin with an uppercase letter or if a class of the same name already exists." | wasPresent oldClass newClass invalidFields invalidMethods |  (self isValidName: newName) ifFalse: [^false]. (wasPresent _ environ includesKey: newName) ifTrue: [oldClass _ environ at: newName. (oldClass isKindOf: Behavior) ifFalse: [environ removeOrBrowse: newName. wasPresent _ false. oldClass _ self newNamed: newName]] ifFalse: [oldClass _ self newNamed: newName]. newClass _ oldClass copy. invalidFields _ changed | (newClass subclassOf: sup oldClass: oldClass instanceVariableNames: instVarString variable: v words: w pointers: p ifBad: [^false]). invalidFields ifFalse: [newClass obsolete. newClass _ oldClass]. invalidMethods _ invalidFields | (newClass declare: classVarString) | (newClass sharing: poolString). commentString == nil ifFalse: [newClass comment: commentString]. (environ includesKey: newName) ifFalse: [environ declare: newName from: Undeclared. environ at: newName put: newClass]. SystemOrganization classify: newClass name under: categoryName asSymbol. newClass validateFrom: oldClass in: environ instanceVariableNames: invalidFields methods: invalidMethods. "Update subclass lists." newClass superclass removeSubclass: oldClass. newClass superclass addSubclass: newClass. "Update Changes." wasPresent ifTrue: [Smalltalk changes changeClass: newClass] ifFalse: [Smalltalk changes addClass: newClass]. ^newClass! subclasses "Answer the receiver's subclasses." | temp | self == Class class ifTrue: ["Meta-Object is exceptional subclass of Class" temp _ thisClass subclasses copy. temp remove: Object class. ^temp collect: [:aSubClass | aSubClass class]]. thisClass == nil ifTrue: [^Set new] ifFalse: [^thisClass subclasses collect: [:aSubClass | aSubClass class]]! ! !Metaclass methodsFor: 'compiling'! scopeHas: name ifTrue: assocBlock ^thisClass scopeHas: name ifTrue: assocBlock! ! !Metaclass methodsFor: 'fileIn-Out'! nonTrivial ^self instVarNames size > 0 or: [methodDict size > 0 or: [self comment size > 0]]! ! Metaclass removeSelector: #instHasMultipleSuperclasses! Metaclass removeSelector: #newNamed:otherSupers:! Metaclass removeSelector: #name:inEnvironment:subclassOf:and:instanceVariableNames:variable:words:pointers:classVariableNames:poolDictionaries:category:comment:changed:! !SystemTracer methodsFor: 'private'! clamp: obj self createHashEntryFor: obj using: Clamped. (obj isKindOf: Behavior) ifTrue: [writeDict at: obj put: #writeClamped:. Smalltalk removeKey: obj name. obj superclass removeSubclass: obj. SystemOrganization removeElement: obj name]! ! Smalltalk removeClassNamed: #MetaclassForMultipleInheritance! Object subclass: #Behavior instanceVariableNames: 'superclass methodDict format subclasses' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !SystemDictionary methodsFor: 'accessing'! removeOrBrowse: aSymbol "Notify the user that the argument, aSymbol, is defined. If it is refered to, then browse references to it. Otherwise simply remove it." | association references | (self includesKey: aSymbol) ifFalse: [^self]. association _ self associationAt: aSymbol. references _ self allCallsOn: association. references isEmpty ifTrue: [self notify: aSymbol , ' already exists. Proceed to redefine.'. self removeKey: aSymbol] ifFalse: [self notify: aSymbol , ' already exists. Proceed to browse references.'. self browseAllCallsOn: association]! ! elf notify: 'Attempt to circularly define ' , newName , '.'. ^false]. ^#F-4d\ggg+, g >: removeMultipleInheritance.st.moveMultipleInheritance.stremoveMultipleInheritance.steView methodsFor: 'initialize-release'! initialize colorRangeCollection _ SortedCollection new. ^super initialize! ! !GraphGaugeView methodsFor: 'displaying'! displayUpdatedView "Display the view of the receiver." | mask | mask _ self newBarColor. (self mustInitializeForm: mask) ifTrue: [self displayGraphForm: (self buildGraphForm: mask). oldInsetDisplayBox _ self insetDisplayBox]. valueCollection addLast: self oldValue. valueCollection size > 1000 ifTrue: [valueCollection removeFirst]. self displayGraphValue: self oldValue! displayView "Display the view of the receiver." self displayUpdatedView! ! !GraphGaugeView methodsFor: 'private'! addColorRangePair: aValueColorPair | thePixelStyle | thePixelStyle _ aValueColorPair colorMask pixelStyle. thePixelStyle background isNil ifTrue: [thePixelStyle foreground: thePixelStyle foreground background: self topView viewStyle pixelStyle background filter: nil planeMask: nil]. colorRangeCollection add: aValueColorPair! buildGraphForm: mask | limit i | self formColor: mask. form _ Form extent: self formExtent. form black. self truncateOldTime. limit _ valueCollection size. limit > oldTime ifTrue: [i _ limit - oldTime] ifFalse: [i _ 1]. oldTime _ 0. ^i! displayGraphForm: index "Display the graph for values in the value collection starting at the value at the index, index." | i limit value box completeForm completeFormBoundingBox | limit _ valueCollection size. i _ index. box _ self insetDisplayBox. completeForm _ Form extent: box extent. completeFormBoundingBox _ completeForm boundingBox. [i <= limit] whileTrue: [value _ ((valueCollection at: i) - self range first * self displayIncrement) rounded. completeForm copyBits: (Rectangle origin: 0 @ 0 extent: (self lineExtent: value)) from: self indicatorForm at: (orientation = #horizontal ifTrue: [0 @ oldTime] ifFalse: [oldTime @ (completeFormBoundingBox height - value)]) clippingBox: completeFormBoundingBox rule: Form over mask: Form black. i _ i + 1. oldTime _ oldTime + 1]. completeForm displayOn: Display at: box origin clippingBox: box rule: Form over mask: self formColor! displayGraphValue: modelValue "Extend the graph for the next value of the model, modelValue." | value yDisp | value _ (modelValue - self range first * self displayIncrement) rounded. oldTime < self maxTimePosition ifFalse: [yDisp _ valueCollection size - (oldTime / 2) rounded. oldTime _ 0. self displayGraphForm: yDisp]. Display copyBits: (Rectangle origin: 0 @ 0 extent: (self lineExtent: value)) from: self indicatorForm at: (orientation = #horizontal ifTrue: [0 @ oldTime + self insetDisplayBox origin] ifFalse: [oldTime @ (self insetDisplayBox height - value) + self insetDisplayBox origin]) clippingBox: self insetDisplayBox rule: Form over mask: self formColor. oldTime _ oldTime + 1! formExtent ^orientation = #horizontal ifTrue: [self lineExtent: self insetDisplayBox width] ifFalse: [self lineExtent: self insetDisplayBox height]! lineExtent: anInteger ^orientation = #horizontal ifTrue: [anInteger @ 1] ifFalse: [1 @ anInteger]! maxTimePosition ^orientation = #horizontal ifTrue: [self insetDisplayBox height] ifFalse: [self insetDisplayBox width]! mustInitializeForm: mask "Answer true if the form needs to be initialized." ^(mask ~= self formColor) | form isNil | (oldInsetDisplayBox ~= self insetDisplayBox)! newBarColor | valuePair | valuePair _ colorRangeCollection findFirst: [:entry | entry value >= self oldValue]. ^valuePair = 0 ifTrue: [Form black] ifFalse: [valuePair _ colorRangeCollection at: valuePair. valuePair colorMask]! oldTime: anInteger oldTime _ anInteger! truncateOldTime orientation = #horizontal ifTrue: [oldTime < self insetDisplayBox height ifFalse: [oldTime _ (self insetDisplayBox height / 2) rounded]] ifFalse: [oldTime < self insetDisplayBox width ifFalse: [oldTime _ (self insetDisplayBox width / 2) rounded]]! valueCollection: anOrderedCollection valueCollection _ anOrderedCollection! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GraphGaugeView class instanceVariableNames: ''! !GraphGaugeView class methodsFor: 'instance creation'! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol barColor: aColor "Return an initialize instance." | view | view _ super on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol barColor: aColor. view oldTime: 0. view valueCollection: (OrderedCollection new: 1000). ^view! ! !GraphGaugeView class methodsFor: 'private'! initialOldValue: aView "Initialize the old value of the view, aView." ^aView range first! ! BarGaugeView subclass: #NeedleGaugeView instanceVariableNames: 'needleDirection' classVariableNames: 'DownNeedleForm LeftNeedleForm RightNeedleForm UpNeedleForm' poolDictionaries: '' category: 'Interface-Gauges'! NeedleGaugeView comment: 'Instances of this class provide a needle gauge view of a numeric aspect of a model. Instance variables: needleDirection #up, #down, #left, #right Class variables: UpNeedleForm
a form containing the upward pointing needle DownNeedleForm a form containing the downward pointing needle LeftNeedleForm a form containing the leftward pointing needle RightNeedleForm a form containing the rightward pointing needle '! !NeedleGaugeView methodsFor: 'accessing'! needleDirection "Return the needleDirection ( #up, #down, #left, or #right ) of the bar." ^needleDirection! ! !NeedleGaugeView methodsFor: 'displaying'! displayView "Display the needle." self eraseNeedle. self displayNeedle! ! !NeedleGaugeView methodsFor: 'needle form access'! eraseNeedleForm "Return a form used to erase the needle." ^(Form extent: self needleForm extent) offset: self needleForm offset! needleForm "Return the proper needleForm" form isNil ifFalse: [^form]. needleDirection = #up ifTrue: [^form _ UpNeedleForm]. needleDirection = #down ifTrue: [^form _ DownNeedleForm]. needleDirection = #left ifTrue: [^form _ LeftNeedleForm]. needleDirection = #right ifTrue: [^form _ RightNeedleForm]. self error: 'needle direction is invalid'! ! !NeedleGaugeView methodsFor: 'private'! displayNeedle "Display the needle." self needleForm displayOn: Display at: self newNeedleLocation clippingBox: self insetDisplayBox rule: Form over mask: Form black! eraseNeedle "Erase the needle." self eraseNeedleForm displayOn: Display at: self oldNeedleLocation clippingBox: self insetDisplayBox rule: Form over mask: Form black! needleDirection: aSymbol "Set the needleDirection ( #up, #down, #left, or #right ) of the bar. " needleDirection _ aSymbol! needleLocation: value "Return the location of the needle in screen coordinates according to value, the current value of the gauge." | y rect x | rect _ self insetDisplayBox. self orientation = #horizontal ifTrue: [self needleDirection = #up ifTrue: [y _ rect top] ifFalse: [y _ rect top - (self needleForm height - rect height)]. ^rect left + (value - self range first * self displayIncrement) rounded @ y] ifFalse: [self needleDirection = #left ifTrue: [x _ rect left] ifFalse: [x _ rect left - (self needleForm width - rect width)]. ^x @ (rect bottom - (value - self range first * self displayIncrement) rounded)]! newNeedleLocation "Return the location in screen coordinates where the needle should be." ^self needleLocation: self currentValue! oldNeedleLocation "Return the location in screen coordinates where the needle was." ^self needleLocation: self oldValue! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! NeedleGaugeView class instanceVariableNames: ''! !NeedleGaugeView class methodsFor: 'class initialization'! initialize "NeedleGaugeView initialize" self initializeUpNeedleForm. self initializeDownNeedleForm. self initializeRightNeedleForm. self initializeLeftNeedleForm! initializeDownNeedleForm "Initialize the needle form pointing down for a horizontal bar. " | pen angle rect extent f | pen _ Pen new. angle _ 20. rect _ 0 @ 0 extent: 100 @ 100. extent _ rect height / (90 - (angle / 2)) tan * 4 @ rect height. f _ Form extent: extent rounded. pen destForm: f. pen place: f boundingBox bottomCenter. pen north. pen turn: 0 - (angle / 2). pen down. pen go: rect height. angle * 2 timesRepeat: [pen place: f boundingBox bottomCenter. pen turn: 0.5. pen go: rect height]. DownNeedleForm _ f offset: 0 - (f width / 2) rounded @ 0! initializeLeftNeedleForm "Initialize the needle form pointing to the left for a vertical bar. " | pen angle rect extent f | pen _ Pen new. angle _ 20. rect _ 0 @ 0 extent: 100 @ 100. extent _ rect width @ (rect width / (90 - (angle / 2)) tan * 4). f _ Form extent: extent rounded. pen destForm: f. pen place: f boundingBox leftCenter. pen north. pen turn: 0 - (90 - (angle / 2)). pen down. pen go: 0 - rect width. angle * 2 timesRepeat:  [pen place: f boundingBox leftCenter. pen turn: -0.5. pen go: 0 - rect width]. LeftNeedleForm _ f offset: 0 @ (0 - (f height / 2) rounded)! initializeRightNeedleForm "Initialize the needle form pointing to the right for a vertical bar." | pen angle rect extent f | pen _ Pen new. angle _ 20. rect _ 0 @ 0 extent: 100 @ 100. extent _ rect width @ (rect width / (90 - (angle / 2)) tan * 4). f _ Form extent: extent rounded. pen destForm: f. pen place: f boundingBox rightCenter. pen north. pen turn: 90 - (angle / 2). pen down. pen go: 0 - rect width. angle * 2 timesRepeat: [pen place: f boundingBox rightCenter. pen turn: 0.5. pen go: 0 - rect width]. RightNeedleForm _ f offset: 0 @ (0 - (f height / 2) rounded)! initializeUpNeedleForm "Initialize the needle form pointing up for a horizontal bar." | pen angle rect extent f | pen _ Pen new. angle _ 20. rect _ 0 @ 0 extent: 100 @ 100. extent _ rect height / (90 - (angle / 2)) tan * 4 @ rect height. f _ Form extent: extent rounded. pen destForm: f. pen place: f boundingBox topCenter. pen north. pen turn: 180 - (angle / 2). pen down. pen go: rect height. angle * 2 timesRepeat: [pen place: f boundingBox topCenter. pen turn: 0.5. pen go: rect height]. UpNeedleForm _ f offset: 0 - (f width / 2) rounded @ 0! ! !NeedleGaugeView class methodsFor: 'instance creation'! on: anObject aspect: aspectMsg change: changedMsg range: anInterval "Return an initialized instance." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: #vertical needleDirection: #left barColor: nil! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: aDirSymbol "Return an initialized instance." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: aDirSymbol barColor: nil! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: aDirSymbol barColor: aColor "Return an initialized instance." | view | view _ super on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol barColor: aColor. view needleDirection: aDirSymbol. ^view! ! !NeedleGaugeView class methodsFor: 'example'! simpleExample "NeedleGaugeView simpleExample" | numberHolder1 bgv1 topView | numberHolder1 _ NumberHolder new value: 0. bgv1 _ NeedleGaugeView on: numberHolder1 aspect: #value change: #value: range: (0 to: 10) orientation: #vertical needleDirection: #right. topView _ StandardSystemView model: nil label: 'Needle GaugeView Example' minimumSize: 20 @ 20. topView borderWidth: 2. topView addSubView: bgv1. topView controller open! ! NeedleGaugeView initialize! View subclass: #GaugeWithScaleView instanceVariableNames: 'gaugeScaleView gaugeView' classVariableNames: '' poolDictionaries: '' category: 'Interface-Gauges'! GaugeWithScaleView comment: 'Instances of this class provide a combined gauge and scale view. Instance variables: gaugeView gaugeScaleView '! !GaugeWithScaleView methodsFor: 'accessing'! gaugeScaleView "Return the gauge scale view of the receiver." ^gaugeScaleView! gaugeView "Return the gauge view of the receiver." ^gaugeView! ! !GaugeWithScaleView methodsFor: 'building'! build: dirSymbol "Assemble the gauge and scale sub views and return a view with them inside." | orientation | orientation _ self gaugeView orientation. orientation = #vertical ifTrue: [dirSymbol isNil | (dirSymbol = #right) ifTrue: [^self buildRightVertical]. dirSymbol = #left ifTrue: [^self buildLeftVertical]]. orientation = #horizontal ifTrue: [dirSymbol isNil | (dirSymbol = #up) ifTrue: [^self buildTopVertical]. dirSymbol = #down ifTrue: [^self buildBottomVertical]]. self error: 'We got a bad input parameter here somewhere!!!!'! ! !GaugeWithScaleView methodsFor: 'private'! buildBottomVertical "Assemble the sub views with the bar/needle gauge on the top, and the scale on the bottom." self addSubView: self gaugeView in: (0 @ 0 corner: 1 @ self gaugeOnTopHeight) borderWidth: 1. self addSubView: self gaugeScaleView in: (0 @ self gaugeOnTopHeight corner: 1 @ 1) borderWidth: 1! buildLeftVertical "Assemble the sub views with the bar/needle gauge on the left, and the scale on the right" self addSubView: self gaugeScaleView in: (0 @ 0 corner: self gaugeOnRightWidth @ 1) borderWidth: 1. self addSubView: self gaugeView in: (self gaugeOnRightWidth @ 0 corner: 1@ 1) borderWidth: 1! buildRightVertical "Assemble the sub views with the bar/needle gauge on the left, and the scale on the right" self addSubView: self gaugeView in: (0 @ 0 corner: (1 - self gaugeOnRightWidth) @ 1) borderWidth: 1. self addSubView: self gaugeScaleView in: ((1 - self gaugeOnRightWidth) @ 0 corner: 1 @ 1) borderWidth: 1! buildTopVertical "Assemble the sub views with the bar/needle gauge on the bottom, and the scale on the top" self addSubView: self gaugeScaleView in: (0 @ 0 corner: 1 @ (1 - self gaugeOnTopHeight)) borderWidth: 1. self addSubView: self gaugeView in: (0 @ (1 - self gaugeOnTopHeight) corner: 1 @ 1) borderWidth: 1! gaugeOnRightWidth "Return the width (scale 0 to 1) of the gauge when vertical and on the right of the scale." ^0.66! gaugeOnTopHeight "Return the top (scale 0 to 1) of the gauge when horizontal and on the top of the scale." ^0.5! gaugeScaleView: aGaugeScaleView "Set the gauge scale view of the receiver." gaugeScaleView _ aGaugeScaleView! gaugeView: aGaugeView "Set the gauge view of the receiver." gaugeView _ aGaugeView! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GaugeWithScaleView class instanceVariableNames: ''! !GaugeWithScaleView class methodsFor: 'instance creation'! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol "Return a gauge view with a scale view." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol scaleOrientation: (aSymbol = #horizontal ifTrue: [#up] ifFalse: [#right])! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol color: aColor "Return a gauge view with a scale view." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol scaleOrientation: (aSymbol = #horizontal ifTrue: [#up] ifFalse: [#right]) color: aColor! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: dirSymbol "Return a needle gauge view with a scale view." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: dirSymbol color: nil! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol needleDirection: dirSymbol color: aColor "Return a needle gauge view with a gauge scale view." | view type | view _ self new. view gaugeView: (NeedleGaugeView on: anObject aspect: aspectMsg change: changedMsg range: (anInterval first to: anInterval last) orientation: aSymbol needleDirection: dirSymbol barColor: aColor). dirSymbol isNil ifTrue: [aSymbol = #horizontal ifTrue: [type _ #up] ifFalse: [type _ #right]] ifFalse: [type _ dirSymbol]. view gaugeScaleView: (self createScaleView: anInterval orientation: type). ^view build: dirSymbol! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol scaleOrientation: anotherSymbol "Return a gauge view with a gauge scale view." ^self on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol scaleOrientation: anotherSymbol color: nil! on: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol scaleOrientation: anotherSymbol color: aColor "Return a gauge view with a gauge scale view." | view | view _ self new. view gaugeView: (self createGaugeViewOn: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol color: aColor). view gaugeScaleView: (self createScaleView: anInterval orientation: anotherSymbol). ^view build: anotherSymbol! ! !GaugeWithScaleView class methodsFor: 'example'! example "GaugeWithScaleView example" | bgv0 bgv1 bgv2 bgv3 bgv7 bgv8 bgv4 bgv5 bgv6 topView | bgv0 _ self on: (NumberHolder new value: 1.8) aspect: #value change: #value: range: (1 to: 3 by: 0.2) orientation: #vertical. bgv1 _ self on: (NumberHolder new value: 7) aspect: #value change: #value: range: (0 to: 10) orientation: #vertical. bgv2 _ self on: (NumberHolder new value: 12.7) aspect: #value change: #value: range: (10 to: 15 by: 0.5) orientation: #vertical needleDirection: #right. bgv3 _ self on: (NumberHolder new value: 325) aspect: #value change: #value: range: (0 to: 1000 by: 100) orientation: #vertical needleDirection: #left. bgv7 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #vertical. bgv8 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #horizontal. bgv4 _ self on: (NumberHolder new value: 2) aspect: #value change: #value: range: (1 to: 5) orientation: #horizontal. bgv5 _ self on: (NumberHolder new value: -3.25) aspect: #value change: #value: range: (-5 to: 5 by: 1) orientation: #horizontal needleDirection: #down. bgv6 _ self on: (NumberHolder new value: 38.6) aspect: #value change: #value: range: (0 to: 100 by: 10) orientation: #horizontal needleDirection: #up. topView _ StandardSystemView model: nil label: self name, ' Example' minimumSize: 600 @ 460. topView borderWidth: 2. topView  addSubView: bgv0 in: (0 @ 0 extent: 0.1665 @ 0.5) borderWidth: 1. topView addSubView: bgv1 in: (0.1665 @ 0 extent: 0.1665 @ 0.5) borderWidth: 1. topView addSubView: bgv2 in: (0.333 @ 0 extent: 0.1665 @ 0.5) borderWidth: 1. topView addSubView: bgv3 in: (0.4995 @ 0 extent: 0.1665 @ 0.5) borderWidth: 1. topView addSubView: bgv7 in: (0.666 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv8 in: (0 @ 0.5 extent: 1 @ 0.125) borderWidth: 1. topView addSubView: bgv4 in: (0 @ 0.625 extent: 1 @ 0.125) borderWidth: 1. topView addSubView: bgv5 in: (0 @ 0.75 extent: 1 @ 0.125) borderWidth: 1. topView addSubView: bgv6 in: (0 @ 0.875 extent: 1 @ 0.125) borderWidth: 1. topView controller open! simpleExample "GaugeWithScaleView simpleExample" | topView bgv | bgv _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (-5 to: 0 by: 1) orientation: #vertical. topView _ StandardSystemView model: nil  label: 'Simple Bar Example' minimumSize: 100 @ 300. topView borderWidth: 2. topView addSubView: bgv. topView controller open! simpleNeedleExample "GaugeWithScaleView simpleNeedleExample" | topView bgv | bgv _ GaugeWithScaleView on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #horizontal needleDirection: #up. topView _ StandardSystemView model: nil label: 'Simple Needle Example' minimumSize: 550 @ 50. topView borderWidth: 2. topView addSubView: bgv. topView controller open! ! !GaugeWithScaleView class methodsFor: 'private'! createGaugeViewOn: anObject aspect: aspectMsg change: changedMsg range: anInterval orientation: aSymbol color: aColor "Return a gauge view." ^self gaugeClass on: anObject aspect: aspectMsg change: changedMsg range: (anInterval first to: anInterval last) orientation: aSymbol barColor: aColor! createScaleView: anInterval orientation: aSymbol "Return a scale view." ^GaugeScaleView range: anInterval orientation: aSymbol! gaugeClass "Return the class of the default gauge view." ^BarGaugeView! ! GaugeWithScaleView subclass: #GraphGaugeWithScaleView instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Interface-Gauges'! GraphGaugeWithScaleView comment: 'Instances of this class provide a combined graph and scale view. '! !GraphGaugeWithScaleView methodsFor: 'building'! gaugeOnRightWidth ^0.15! gaugeOnTopHeight ^0.85! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GraphGaugeWithScaleView class instanceVariableNames: ''! !GraphGaugeWithScaleView class methodsFor: 'instance creation'! gaugeClass "Return the class of the default gauge view." ^GraphGaugeView! ! !GraphGaugeWithScaleView class methodsFor: 'example'! colorExample "GraphGaugeWithScaleView colorExample" | bgv0 bgv1 bgv7 bgv8 bgv4 topView bv0 bv1 bv7 bv8 bv4 | bgv0 _ self on: (NumberHolder new value: 1.8) aspect: #value change: #value: range: (1 to: 3 by: 0.2) orientation: #vertical scaleOrientation: #left. bv0 _ bgv0 gaugeView. bv0 addColorRangePair: (ValueColorPair value: 1.4 color: (Halftone with: 8)). bv0 addColorRangePair: (ValueColorPair value: 1.6 color: (Halftone with: 12)). bv0 addColorRangePair: (ValueColorPair value: 2 color: (Halftone with: 10)). bv0 addColorRangePair: (ValueColorPair value: 2.5 color: (Halftone with: 11)). bv0 addColorRangePair: (ValueColorPair value: 3 color: (Halftone with: 9)). bgv1 _ self on: (NumberHolder new value: 7) aspect: #value change: #value: range: (0 to: 10) orientation: #vertical. bv1 _ bgv1 gaugeView. bv1 addColorRangePair: (ValueColorPair value: 3 color: (Halftone with: 8)). bv1 addColorRangePair: (ValueColorPair value: 4 color: (Halftone with: 12)). bv1 addColorRangePair: (ValueColorPair value: 5 color: (Halftone with: 10)). bv1 addColorRangePair: (ValueColorPair value: 6 color: (Halftone with: 11)). bv1 addColorRangePair: (ValueColorPair value: 10 color: (Halftone with: 9)). bgv7 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #vertical scaleOrientation: #right. bv7 _ bgv7 gaugeView. bv7 addColorRangePair: (ValueColorPair value: 97 color: (Halftone with: 8)). bv7 addColorRangePair: (ValueColorPair value: 98 color: (Halftone with: 12)). bv7 addColorRangePair: (ValueColorPair value: 99 color: (Halftone with: 10)). bv7 addColorRangePair: (ValueColorPair value: 100 color: (Halftone with: 11)). bv7 addColorRangePair: (ValueColorPair value: 101 color: (Halftone with: 9)). bgv8 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #horizontal scaleOrientation: #down. bv8 _ bgv8 gaugeView. bv8 addColorRangePair: (ValueColorPair value: 97 color: (Halftone with: 8)). bv8 addColorRangePair: (ValueColorPair value: 98 color: (Halftone with: 12)). bv8 addColorRangePair: (ValueColorPair value: 99 color: (Halftone with: 10)). bv8 addColorRangePair: (ValueColorPair value: 100 color: (Halftone with: 11)). bv8 addColorRangePair: (ValueColorPair value: 101 color: (Halftone with: 9)). bgv4 _ self on: (NumberHolder new value: 2) aspect: #value change: #value: range: (1 to: 5) orientation: #horizontal. bv4 _ bgv4 gaugeView. bv4 addColorRangePair: (ValueColorPair value: 2 color: (Halftone with: 8)). bv4 addColorRangePair: (ValueColorPair value: 2.5 color: (Halftone with: 12)). bv4 addColorRangePair: (ValueColorPair value: 3 color: (Halftone with: 10)). bv4 addColorRangePair: (ValueColorPair value: 4 color: (Halftone with: 11)). bv4 addColorRangePair: (ValueColorPair value: 5 color: (Halftone with: 9)). topView _ StandardSystemView model: nil label: self name, ' Example' minimumSize: 600 @ 460. topView borderWidth: 2. topView addSubView: bgv0 in: (0 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv1 in: (0.333 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv7 in: (0.666 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv8 in: (0 @ 0.5 extent: 1 @ 0.25) borderWidth: 1. topView addSubView: bgv4 in: (0 @ 0.75 extent: 1 @ 0.25) borderWidth: 1. topView controller open! example "GraphGaugeWithScaleView example" | bgv0 bgv1 bgv7 bgv8 bgv4 topView | bgv0 _ self on: (NumberHolder new value: 1.8) aspect: #value change: #value: range: (1 to: 3 by: 0.2) orientation: #vertical scaleOrientation: #left. bgv1 _ self on: (NumberHolder new value: 7) aspect: #value change: #value: range: (0 to: 10) orientation: #vertical. bgv7 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5) orientation: #vertical scaleOrientation: #right. bgv8 _ self on: (NumberHolder new value: 98.6) aspect: #value change: #value: range: (96.0 to: 101.0 by: 0.5)  orientation: #horizontal scaleOrientation: #down. bgv4 _ self on: (NumberHolder new value: 2) aspect: #value change: #value: range: (1 to: 5) orientation: #horizontal. topView _ StandardSystemView model: nil label: self name, ' Example' minimumSize: 600 @ 460. topView borderWidth: 2. topView addSubView: bgv0 in: (0 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv1 in: (0.333 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv7 in: (0.666 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv8 in: (0 @ 0.5 extent: 1 @ 0.25) borderWidth: 1. topView addSubView: bgv4 in: (0 @ 0.75 extent: 1 @ 0.25) borderWidth: 1. topView controller open! ! ColorRangePair: (ValueColorPair value: 4 color: (Halftone with: 12)). bv1 addColorRangePair: (ValueColorPair value: 5 color: (Halftone with: 10)). bv1 addColorRangePair: (ValueColorPair value: 6 color: (Halftone with: 11)). bv1 addColorRangePair: (ValueColo#F-6d\g &Interface-Gauges.st.terface-Gauges.stInterface-Gauges.stbgv7 in: (0.666 @ 0 extent: 0.333 @ 0.5) borderWidth: 1. topView addSubView: bgv8 in: (0 @ 0.5 extent: 1 @ 0.25) borderWidth: 1. topView addSubView: bgv4 in: (0 @ 0.75 extent: 1 @ 0.25) borderWidth: 1. topView controller open! ! ColorRangePair: (ValueColorPair value: 4 color: (Halftone with: 12)). bv1 addColorRangePair: (ValueColorPair value: 5 color: (Halftone with: 10)). bv1 addColorRangePair: (ValueColorPair value: 6 color: (Halftone with: 11)). bv1 addColorRangePair: (ValueColorPa#F-d\g..x . &6Interface-GraphGauges.st.terface-GraphGauges.stInterface-GraphGauges.stand then the ^U is unnecessary: repetition count arguments may be entered just as a string of digits. .PP The following commands are only valid when the character and entry cursors are the same. That is, when no long command is being entered. Most of them introduce a new long command. .IP = Prompts for an expression which will be evaluated dynamically to produce a value for the entry pointed at by the entry cursor. This may be used in conjunction with ^V to make one entries value be dependent on anothers. .IP ? Types a brief helpful message. .IP " Enter a label for the current entry. .IP e Edit the value associated with the current entry. This is identical to '=' except that the command line starts out containing the old value or expression associated with the entry. .IP < Associate a string with this entry that will be flushed left against the left edge of the entry. .IP > Associates a string with this entry that will be flushed right against the right edge of the entry. .IP g Get a new database from a named file. .IP p Put the current database onto a named file. .IP w Write a listing of the current database in a form that matches its appearance on the screen. This differs from the "put" command in that "put"s files are intended to be reloaded with "get", while "write" produces a file for people to look at. .IP f Sets the output format to be used for printing the numbers in each entry in the current column. Type in two numbers which will be the width in characters of a column and the number of digits which will follow the decimal point. .IP r Create a new row by moving the row containing the entry cursor, and all following, down one. The new row will be empty. .IP c Create a new column by moving the column containing the entry cursor, and all following, right one. The new column will be empty. .IP d Delete this row. .IP D Delete this column. .PP Expressions that are used with the '=' and 'e' commands have a fairly conventional syntax. Terms may be variable names (from the ^V command), parenthesised expressions, negated terms, and constants. The +/ term sums values in rectangular regions of the table (the notation +/ is reminiscent of apl's additive reduction.) Terms may be combined using many binary operators. Their precedences (from highest to lowest) are: *,/; +,-; <,=,>,<=,>=; &; |; ?. .TP 15 e+e Addition. .TP 15 e-e Subtraction. .TP 15 e*e Multtplication. .TP 15 e/e Division. .TP 15 +/v:v Sum all valid (nonblank) entries in the region whose two corners are defined by the two variable (entry) names given. .TP 15 e?e:e Conditional: If the first expression is true then the value of the second is returned, otherwise the value of the third is. .TP 15 <,=,>,<=,>= Relationals: true iff the indicated relation holds. .TP 15 &,| Boolean connectives. .SH FILES expense.sc \- a sample expense report. .SH SEE ALSO bc(1), dc(1), the VisiCalc or T/Maker manuals. .SH BUGS There should be a */ operator. Expression evaluation is dependency directed: if an expression refers to an expression that is defined later in the spreadsheet, all is well, it will be evaluated properly. Difficulties only occur where there are circular dependencies in the expression graph. e entry cursor backward one column. .IP ^C Exit from \fIsc\fR. .IP ^G Abort the current long command. .IP ^H Backspace one character. .IP ^L Redraw the screen. .IP ^J Creates a new row immediatly following the current row. It is initialized to be a copy of the current row, with all variable references moved down one row. If an e*/  *0 sc.cscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czc"/****************************************\ * * * SC A Spreadsheet Calculator * * Main driver * * * * James Gosling, September 1982 * * * \****************************************/ #include #include "sc.h" int linelim = -1; error (fmt,a,b,c,d,e) { move (1,0); clrtoeol (); printw (fmt,a,b,c,d,e); } int seenerr; yyerror (err) char *err; { if (seenerr) return; seenerr++; move (1,0); clrtoeol (); printw ("%s: %.*s<=%s",err,linelim,line,line+linelim); } struct ent *lookat(row,col){ register struct ent **p; /* Added check to be sure row and col are within bounds before looking up the variable reference (next 2 lines) KB 3/12/83 */ if (row>MAXROWS-1) row = MAXROWS-1; if (col>MAXCOLS-1) col = MAXCOLS-1; p = &tbl[row][col]; if (*p==0) { *p = (struct ent *) malloc (sizeof (struct ent)); if (row>maxrow) maxrow = row; if (col>maxcol) maxcol = col; (*p)->label = 0; (*p)->evaltime = 0; (*p)->flags = 0; (*p)->row = row; (*p)->col = col; (*p)->expr = 0; } return *p; } update () { register row, col; register struct ent **p; static lastmx, lastmy; int maxcol; int rows = LINES - 2; int cols; if (curcol < stcol) stcol = curcol, FullUpdate++; if (currow < strow) strow = currow, FullUpdate++; while (1) { register i; /* Changed test for overflow of COLS to prevent wrap around KB 3/12/83 for (i = stcol, cols = 0, col = 0; col < COLS - 4 && i < MAXCOLS; i++) col += fwidth[i], cols++; */ for (i=stcol, cols=0, col=0; col+fwidth[i] < COLS && i= stcol + cols) stcol++, FullUpdate++; else break; } if (currow >= strow + rows) strow = currow - rows + 1, FullUpdate++; if (FullUpdate) { move (2, 0); clrtobot (); } maxcol = stcol + cols - 1; for (row = strow + rows - 1; row >= strow; row--) { register c = 0; for (p = &tbl[row][col = stcol]; col <= maxcol; col++, p++) { if (*p && ((*p) -> flags & is_changed || FullUpdate)) { register r = row - strow + 2; char *s; move (r, c); (*p) -> flags &= ~is_changed; if ((*p) -> flags & is_valid) printw ("%*.*f", fwidth[col], precision[col], (*p) -> v); if (s = (*p) -> label) mvaddstr (r, (*p) -> flags & is_leftflush ? c : c - strlen (s) + fwidth[col], s); } c += fwidth[col]; } } mvaddstr (lastmy, lastmx, " "); lastmy = currow - strow + 2; lastmx = 0; for (col = stcol; col <= curcol;) lastmx += fwidth[col++]; mvaddstr (lastmy, lastmx, "<"); move (0, 0); clrtoeol (); if (linelim >= 0) { addstr (">> "); addstr (line); } else move (lastmy, lastmx); FullUpdate = 0; } #define ctl(c) ('c'&037) main (argc, argv) char **argv; { int running = 1; register char c; int edistate = -1; int arg = 1; int narg; int nedistate = -1; { register i; for (i = 0; i < MAXCOLS; i++) { fwidth[i] = DFT_WIDTH; precision[i] = DFT_PREC; } } initscr (); clear (); raw (); noecho (); error ("Welcome to the Spreadsheet Calculator, type '?' for help."); if (argc > 1) readfile (argv[1]); while (running) { nedistate = -1; narg = 1; if (edistate < 0 && linelim < 0 && (changed || FullUpdate)) EvalAll (), changed = 0; update (); refresh (); move (1, 0); clrtoeol (); fflush (stdout); seenerr = 0; if ((c = getchar ()) < ' ') switch (c) { default: error ("\007No such command (^%c)", c + 0100); break; case ctl (b): while (--arg>=0) if (curcol) curcol--; break; case ctl (c): if (DBchanged) { mvaddstr (1,0, "Are you sure you want to exit, you've made changes to the Spreadsheet? "); refresh (); running = getchar () != 'y'; } else running = 0; break; case ctl (f): while (--arg>=0) if (curcol < MAXCOLS - 1) curcol++; break; case ctl (g): linelim = -1; break; case ctl (h): case 0177: while (--arg>=0) if (linelim > 0) line[--linelim] = 0; break; case ctl (j): if (currow >= MAXROWS - 1 || maxcol >= MAXCOLS - 1) { error ("\007The table can't be any bigger"); break; } currow++; openrow (currow); for (curcol = 0; curcol <= maxcol; curcol++) { register struct ent *p = tbl[currow - 1][curcol]; if (p) { register struct ent *n; n = lookat (currow, curcol); n -> v = p -> v; n -> flags = p -> flags; n -> expr = copye (p -> expr, 1, 0); n -> label = 0; n -> evaltime = 0; if (p -> label) { n -> label = (char *) malloc (strlen (p -> label) + 1); strcpy (n -> label, p -> label); } } } for (curcol = 0; curcol <= maxcol; curcol++) { register struct ent *p = tbl[currow][curcol]; if (p && (p -> flags & is_valid) && !p -> expr) break; } if (curcol > maxcol) curcol = 0;  break; case ctl (l): FullUpdate++; break; case ctl (m): if (linelim < 0) line[linelim = 0] = 0; else { linelim = 0; yyparse (); linelim = -1; } break; case ctl (n): while (--arg>=0) if (currow < MAXROWS - 1) currow++; break; case ctl (p): while (--arg>=0) if (currow) currow--; break; case ctl (q): break; /* ignore flow control */ case ctl (s): break; /* ignore flow control */ case ctl (u):  narg = arg * 4; nedistate = 1; break; case ctl (v): if (linelim > 0) { sprintf (line + linelim, "r%dc%d", currow, curcol); linelim = strlen (line); } break; } else if ('0' <= c && c <= '9' && (linelim < 0 || edistate >= 0)) { if (edistate != 0) arg = 0; nedistate = 0; narg = arg * 10 + (c - '0'); } else if (linelim >= 0) { line[linelim++] = c; line[linelim] = 0; } else switch (c) { /* Added check for invalid alpha command KB 3/12/83 */ default: error ("\007No such command (%c)", c); break; case '.': nedistate = 1; break; case '=': sprintf (line, "let r%dc%d = ", currow, curcol); linelim = strlen (line); break; case '?': help (); break; case '"': sprintf (line, "label r%dc%d = \"", currow, curcol); linelim = strlen (line); break; case '<': sprintf (line, "leftstring r%dc%d = \"",  currow, curcol); linelim = strlen (line); break; case '>': sprintf (line, "rightstring r%dc%d = \"", currow, curcol); linelim = strlen (line); break; case 'e': editv (currow, curcol); break; case 'f': sprintf (line, "format [for column] %d [is] ", curcol); linelim = strlen (line); break; case 'p': sprintf (line, "put [database into] \""); linelim = strlen (line); break; case 'g':  sprintf (line, "get [database from] \""); linelim = strlen (line); break; case 'w': sprintf (line, "write [listing to] \""); linelim = strlen (line); break; case 'r': while (--arg>=0) openrow (currow); break; case 'd': while (--arg>=0) closerow (currow); break; case 'c': while (--arg>=0) opencol (curcol); break; case 'D': while (--arg>=0) closecol (curcol); break; } edistate = nedistate;  arg = narg; } move (LINES - 1, 0); refresh (); noraw (); echo (); endwin (); } writefile (fname) char *fname; { register FILE *f = fopen (fname, "w"); register struct ent **p; register r, c; if (f==0) { error ("\007Can't create %s", fname); return; } fprintf (f, "# This data file was generated by the Spreadsheet Calculator.\ \n# You almost certainly shouldn't edit it.\n\n"); for (c=0; clabel) fprintf (f, "%sstring r%dc%d = \"%s\"\n", (*p)->flags&is_leftflush ? "left" : "right", r,c,(*p)->label); if ((*p)->flags&is_valid) { editv (r, c); fprintf (f, "%s\n",line); } } } DBchanged = 0; fclose (f); } readfile (fname) char *fname; { register FILE *f = fopen (fname, "r"); if (f==0) { error ("\007Can't read %s", fname); return; } erasedb (); while (fgets(line,sizeof line,f)) { linelim = 0; if (line[0] != '#') yyparse (); } fclose (f); DBchanged = 0; linelim = -1; } erasedb () { register r, c; for (c = 0; c=0; p++) if (*p) { if ((*p)->expr) efree ((*p) -> expr); if ((*p)->label) free ((*p) -> label); free (*p); *p = 0; } } maxrow = 0; maxcol = 0; FullUpdate++; } openrow (rs) { register r; register struct ent **p; register c; /* changed maxcol MAXCOLS to maxrow MAXROWS KB 3/3/83 */ if (maxrow >= MAXROWS - 1) { error ("\007The table can't have any more rows"); return; } for (r = ++maxrow; r > rs; r--) for (c = maxcol + 1, p = &tbl[r][0]; --c >= 0; p++) if (p[0] = p[-MAXCOLS]) p[0] -> row++; p = &tbl[rs][0]; for (c = maxcol + 1; --c >= 0;) *p++ = 0; FullUpdate++; } closerow (r) register r; { register struct ent **p; register c; while (r=0; p++) if (p[0] = p[MAXCOLS]) p[0]->row--; r++; } p = &tbl[maxrow][0]; for (c=maxcol+1; --c>=0; ) *p++ = 0; maxrow--; FullUpdate++; } opencol (cs) { register r; register struct ent **p; register c; register lim = maxcol-cs+1; /* added maxcol check  KB 3/3/83 */ if (maxcol >= MAXCOLS - 1) { error ("\007The table can't have any more columns"); return; } for (r=0; r<=maxrow; r++) { p = &tbl[r][maxcol+1]; for (c=lim; --c>=0; p--) if (p[0] = p[-1]) p[0]->col++; p[0] = 0; } maxcol++; FullUpdate++; } closecol (cs) { register r; register struct ent **p; register c; register lim = maxcol-cs; for (r=0; r<=maxrow; r++) { p = &tbl[r][cs]; for (c=lim; --c>=0; p++) if (p[0] = p[1]) p[0]->col++; p[0] = 0; } maxcol--; FullUpdate++; } ; break; case '>': sprintf (line, "rightstring r%dc%d = \"", currow, curcol); linelim = strlen (line); break; case 'e': editv (currow, curcol); break; case 'f': sprintf (line, "format [for column] %d [is] ", curcol); linelim = strlen (line); break; case 'p': sprintf (line, "put [database into] \""); linelim = strlen (line); break; case 'g':    sc.hscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czh" /* TC A Table Calculator * Common definitions * * James Gosling, September 1982 * */ #define MAXROWS 50 #define MAXCOLS 40 /* Added constants for default column width and precision here and used them in sc.c KB 3/12/82 */ #define DFT_WIDTH 10 #define DFT_PREC 2 struct ent { double v; char *label; struct enode *expr; short flags; short evaltime; char row, col; }; struct enode { int op; union { double k; struct ent *v; struct { struct enode *left, *right; } o; } e; }; /* op values */ #define O_VAR 'v' #define O_CONST 'k' #define O_REDUCE(c) (c+0200) /* flag values */ #define is_valid 0001 #define is_changed 0002 #define is_lchanged 0004 #define is_leftflush 0010 struct ent *tbl[MAXROWS][MAXCOLS]; int strow, stcol; int currow, curcol; int FullUpdate; int maxrow, maxcol; int fwidth[MAXCOLS]; int precision[MAXCOLS]; char line[1000]; int linelim; int changed; int DBchanged; struct enode *new(); struct ent *lookat(); struct enode *copye(); S|  S}  sc.oscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czo"$ 8ݬݬݬݬ ݬݬXRPPݏCݬݏg1Ѭ11Ѭ''ŏPPxQQPP[kX#PkѬЬѬЬkPԠkPkPkPkPkPԠ kP1m10PPyXԭZHlZPPcX(HUZ֭XEP>P5/!PPíPPPPPPPPP[[1Xŏ[PPZxZQQPPYZ1i1iPog[PPPWXWUNiPiPp~J3J,ݏiPРWiPXPݭPíXPJPPݭWPPݭJXZY1 [1#!PPݏ|uojPPPSZZKJBZ' PPݏ  (ݏݏ1/^1 1 [[( KlKd[YSL I>8PP0ݏ$ݏݏѬЬPݠ խ1խ%  }wpݏc]WSPL`P ݏ6PP 1P1P@PPݏ% 1׭1vPPݏ=P`P ݏPyPPPԭ1׭_'V1 1׭  P@&11 'ݏ11PQďQQxPPPQa[[a4PZpkjݫ P Ԫի&ݫfPP[PݫݪJD1[;50=(PŏQQxPPPQa[[ ի 1p1g  P@z l 12׭11׭yq111xPP1 ;HBݏPP'ݏP1P 16JP1 P1 P11P1u1P 1 P11P 11P1K P1& P11zP1)1oP14 P11ZP1*1K1H1L049."խ!խԭԭ PQ0QQPP1' P@P@1P1~ݏ11ݏݏݏPv11ݏݏ~ݏqP61Ka[ݏݏHݏ;P1+%ݏݏݏP11ݏݏݏP1ݏ+ݏݏPZ1oݏAݏxݏkP01EݏWݏNݏAP1׭,1׭v1׭1׭J1PcKP=1 P.1 P"11P<1B1P?1 P>1c1PD1Pg1,Pe1pPd1=1bPf1i1SPr1Pp1|16Pw11'1$ЭЭ13PP PPPݏݏ^11%ݏlݬmP[[ݬݏnVݏ[FXX(7H8  H.H$HXݏ[ XYY1ŏYPPPZXXpjejPՠ4jPݠXYjP PPPݏ[jP XYݏݏ[tXZY1bb[Y1wݏ!ݬ@P[[ݬݏ#)K[ݏݏ P#[1ZZ JJZ[[_ŏ[PPPYZZ>i5iPՠ  iPݠ qiPՠ iPݠ\iSiY[B<61a1'1ݏ2 PP[[7PPYŏ[PPPZY`jjPZ[ŏPPPZPPYYԊ1lzЬ[[7PPYŏ[PPPZYʠjjPZ[ŏEPPPZ3PPYYԊ!|ì PPPX'ݏV[[?ŏ[PPQxQQQPPZXYYЪjjPZj[\ìPPX[[}8ŏ[PPxQQPPZXYYЪjjPZj[=7%s: %.*s<=%s%*.*f <>> Welcome to the Spreadsheet Calculator, type '?' for help.No such command (^%c)Are you sure you want to exit, you've made changes to the Spreadsheet? The table can't be any biggerr%dc%dNo such command (%c)let r%dc%d = label r%dc%d = "leftstring r%dc%d = "rightstring r%dc%d = "format [for column] %d [is] put [database into] "get [database from] "write [listing to] "wCan't create %s# This data file was generated by the Spreadsheet Calculator. # You almost certainly shouldn't edit it. format %d %d %d %sstring r%dc%d = "%s" leftright%s rCan't read %sThe table can't have any more rowsThe table can't have any more columns    7 D M W ^ d k q v  |  < G L T Y _ e j~ r w~ }         ~   ~      # ) :~ G~ \| c  ~         & 7 > E Y_e l z  ~             #) 0 6 < C KQW ^ d   S  U W X X Y W Z [ W ] W Z [   ;C K Tg Z ag nj x    n o  n n n n r     ' 5; B H Oj Un ]n dn on vr           ! , 4 B| W ] d}          |     ' 08>F NU \j s                 % + 1 7 >  D K  R \  e k q w ~               # ) 0  6 =  D M S Z  ` g  n w }                 j  W X ' W 7 Y = W C Z J [ Q W X ] ^ W d Z k [ r 7  A    N  N |  DMV_N s  y N  b A  s   b  "4 > F S c| m           | B| M _ s | |  |        &| . ] c r  |   d +=`z  }P     " ( . 4 : @ F L R X ^ d j p v |                        # * 1 8 ? F M T [ b i p w ~                       " . < J Y _ e m z  (            ( (    @$ - 4 = D N V ` h v                 - 8 $A H O T  Y ^ c h DDm u D| D" D;   $> >  DBDBDKDQDbDoD $     D"D# @ D$D%D&D'D(D)D* D+D,D-D. D/D0D1D2&D3,D4,D500 $4 4 D79D89 @ D99 @ D:9! @ D;9' (1 D<96 (@ D=9E D>9N U D?E\ D@EEDARDBcDCpDDDEc @DFDGDHDIDJh DKDLDMDNDODPDQDRDSDT DUn DV'DW'DX6DYPy @DZRRD[{D\~ @D] D^D_D`DaDbDcDdDeDf  DgBBDhBDiJDjRRDkWDlDmDnDoDpDqDr DsDt!Du4DvGDwGDxIDybDzhh $p p    DuDu Dy Dy D} D D DD @ DDDDDD D D    & D, DDD5 D$D,D0D4DQ? D^DeH DrDDR X DD` DDDDDDDD DDDDFDSDDDDDDDDDDDDDDDDDDDDDDi DD*r @ DQQDUx @ DUUDkDnDs~ DDDDD DDDDD @ DDDDDD"D%D%D+D.D.D6DJDLDR DYD`D`DcDcDqDwD|D|DDDDDDDDDDDDD DDDDD D D D D D D D D D D D  D  D  D  D  D D D D D D# D# DB DV DY DY D` Dc Dc D D D D D  D! D" D# D$ D% D& D' D( D) D* D+  D, D- D.4 D/H D0K D1K D2^ D3r D4u D5u D6 D7 D8 D9 D: D; D< D= D> D? D@ hDA DB DC DD DE DF jDG" DH% DI DJ DK DL DM DN DON DPo DQv v  $~ ~  DT DU @  DV  @ DW  @  @DX  DY DZ D[ D\ D]  D^ D_ D` Da DbDcDd#De'Df/Dg/Dh/DicDjlDkwDlDmDnDoDp( Dq0 $< F DtDuK @ DvDwDxDyDzQ *D{Z D|D}D~DDDD&&a $*l D/D/q @ v @ D//D:DBDJDNDY{ @ DkkDvDz D DDDDDDDD $  DD @ D @ D @ DDDDDDDD!D(D.DJDYD]Dcc $h @  DpDp @ Dp @ DppDyDDDDDDDDD $  DD @ D @ D @ D@DDDDDDDD=DDDJDPDWD[DaDgg$jDnDn@ Dn#@ Dn)@ Dn.@DzzDDDDDDDDD5sc.cint:t1=r1;-2147483648;2147483647;char:t2=r2;0;127;long:t3=r1;-2147483648;2147483647;short:t4=r1;-32768;32767;unsigned char:t5=r1;0;255;unsigned short:t6=r1;0;65535;unsigned long:t7=r1;0;-1;unsigned int:t8=r1;0;-1;float:t9=r1;4;0;double:t10=r1;8;0;void:t11=11???:t12=1_iobuf:T13=s20_cnt:1,0,32;_ptr:14=*2,32,32;_base:14,64,32;_bufsiz:1,96,32;_flag:4,128,16;_file:2,144,8;;ttychars:T15=s14tc_erase:2,0,8;tc_kill:2,8,8;tc_intrc:2,16,8;tc_quitc:2,24,8;tc_startc:2,32,8;tc_stopc:2,40,8;tc_eofc:2,48,8;tc_brkc:2,56,8;tc_suspc:2,64,8;tc_dsuspc:2,72,8;tc_rprntc:2,80,8;tc_flushc:2,88,8;tc_werasc:2,96,8;tc_lnextc:2,104,8;;tchars:T16=s6t_intrc:2,0,8;t_quitc:2,8,8;t_startc:2,16,8;t_stopc:2,24,8;t_eofc:2,32,8;t_brkc:2,40,8;;ltchars:T17=s6t_suspc:2,0,8;t_dsuspc:2,8,8;t_rprntc:2,16,8;t_flushc:2,24,8;t_werasc:2,32,8;t_lnextc:2,40,8;;sgttyb:T18=s6sg_ispeed:2,0,8;sg_ospeed:2,8,8;sg_erase:2,16,8;sg_kill:2,24,8;sg_flags:4,32,16;;winsize:T19=s8ws_row:6,0,16;ws_col:6,16,16;ws_xpixel:6,32,16;ws_ypixel:6,48,16;;SGTTY:t18AM:G2BS:G2CA:G2DA:G2DB:G2EO:G2HC:G2HZ:G2IN:G2MI:G2MS:G2NC:G2NS:G2OS:G2UL:G2XB:G2XN:G2XT:G2XS:G2XX:G2AL:G14BC:G14BT:G14CD:G14CE:G14CL:G14CM:G14CR:G1 4CS:G14DC:G14DL:G14DM:G14DO:G14ED:G14EI:G14K0:G14K1:G14K2:G14K3:G14K4:G14K5:G14K6:G14K7:G14K8:G14K9:G14HO:G14IC:G14IM:G14IP:G14KD:G14KE:G14KH:G14KL:G14KR:G14KS:G14KU:G14LL:G14MA:G14ND:G14NL:G14RC:G14SC:G14SE:G14SF:G14SO:G14SR:G14TA:G14TE:G14TI:G14UC:G14UE:G14UP:G14US:G14VB:G14VS:G14VE:G14AL_PARM:G14DL_PARM:G14UP_PARM:G14DOWN_PARM:G14LEFT_PARM:G14RIGHT_PARM:G14PC:G2GT:G2NONL:G2UPPERCASE:G2normtty:G2_pfast:G2_win_st:T20=s40_cury:4,0,16;_curx:4,16,16;_maxy:4,32,16;_maxx:4,48,16;_begy:4,64,16;_begx:4,80,16;_flags:4,96,16;_ch_off:4,112,16;_clear:2,128,8;_leave:2,136,8;_scroll:2,144,8;_y:21=*14,160,32;_firstch:22=*4,192,32;_lastch:22,224,32;_nextp:23=*20,256,32;_orig:23,288,32;;My_term:G2_echoit:G2_rawmode:G2_endwin:G2Def_term:G14LINES:G1COLS:G1_tty_ch:G1_res_flg:G1_tty:G18stdscr:G23curscr:G23ent:T24=s24v:10,0,64;label:14,64,32;expr:26=*25,96,32;flags:4,128,16;evaltime:4,144,16;row:2,160,8;col:2,168,8;;enode:T25=s12op:1,0,32;e:27=u8k:10,0,64;v:28=*24,0,32;o:29=s8left:30=*25,0,32;right:30,32,32;;,0,64;;,32,64;;tbl:G31=ar1;0;49;32=ar1;0;39;28_tblstrow:G1_strowstcol:G1_stcolcurrow:G1_currowcurcol:G1_curcolFullUpdate:G1_FullUpdatemaxrow:G1_maxrowmaxcol:G1_maxcolfwidth:G33=ar1;0;39;1_fwidthprecision:G33_precisionline:G34=ar1;0;999;2_linelinelim:G1_linelimchanged:G1_changedDBchanged:G1_DBchangederror:F1_errorfmt:p1a:p1b:p1c:p1d:p1e:p1L146_stdscr_wmove_wclrtoeol_printwseenerr:G1_seenerryyerror:F1_yyerrorerr:p14L155lookat:F28_lookatrow:p1col:p1L161p:r35=*28_mallocupdate:F1_updateL172row:r1col:r1p:r35lastmx:V1L176lastmy:V1L177maxcol:1rows:1_LINEScols:1i:r1_COLS_wclrtobotc:r1r:r1s:14_strlen_waddstrmain:F1_mainargc:p1argv:p21L211running:1c:2edistate:1arg:1narg:1nedistate:1i:r1_initscr_wclear__tty__rawmode__pfast__tty_ch_stty__echoit_readfile_EvalAll_wrefresh__iob_fflush__filbuf_openrowp:r28n:r28_copye_strcpyp:r28_yyparse_sprintf_help_editv_closerow_opencol_closecol_endwinwritefile:F1_writefilefname:p14L349f:r36=*13_fopenp:r35r:r1c:r1_fprintf_fclosereadfile:F1fname:p14L377f:r36_erasedb_fgetserasedb:F1L388r:r1c:r1p:r35_efree_freeopenrow:F1rs:p1L406r:r1p:r35c:r1closerow:F1r:r1r:p1L422p:r35c:r1opencol:F1cs:p1L435r:r1p:r35c:r1lim:r1closecol:F1cs:p1L448r:r1p:r35c:r1lim:r1DDDDDD=DDDJDPDWD1  2  sres.sedscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czd"/%token.*S_/!d /%token.*S_\(.*\)/s// "\1", S_\1,/ p:r35=*28_mallocupdate:F1_updateL172row:r1col:r1p:r35lastmx:V1L176lastmy:V1L177maxcol:1rows:1_LINEScols:1i:r1_COLS_wclrtobotc:r1r:r1s:14_strlen_waddstrmain:F1_mainargc:p1argv:p21L211running:1c:2edistate:1arg:1narg:1nedistate:1i:r1_initscr_wclear__tty__rawmode__pfast__tty_ch_stty__echoit_readfile_EvalAll_wrefresh__iob_fflush__filbuf_openrowp:r28n:r28_copye_strcpyp:r28_yyparse_sprintf_help_editv_close    statres.hscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czh"  "FORMAT", S_FORMAT, "LABEL", S_LABEL, "LEFTSTRING", S_LEFTSTRING, "RIGHTSTRING", S_RIGHTSTRING, "GET", S_GET, "PUT", S_PUT, "LET", S_LET, "WRITE", S_WRITE, cols:1i:r1_COLS_wclrtobotc:r1r:r1s:14_strlen_waddstrmain:F1_mainargc:p1argv:p21L211running:1c:2edistate:1arg:1narg:1nedistate:1i:r1_initscr_wclear__tty__rawmode__pfast__tty_ch_stty__echoit_readfile_EvalAll_wrefresh__iob_fflush__filbuf_openrowp:r28n:r28_copye_strcpyp:r28_yyparse_sprintf_help_editv_close=  >  tagsscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czs"EvalAll interp.c ?^EvalAll () {$? EvalVar interp.c ?^double EvalVar (p)$? Msc sc.c ?^main (argc, argv)$? O_REDUCE sc.h ?^#define O_REDUCE(c) (c+0200)$? closecol sc.c ?^closecol (cs) {$? closerow sc.c ?^closerow (r)$? constant interp.c ?^constant (e)$? copye interp.c ?^struct enode *copye (e, Rdelta, Cdelta)$? ctl sc.c ?^#define ctl(c) ('c'&037)$? debug lex.c ?^debug (fmt, a, b, c) {$? decodev interp.c ?^decodev (v)$? decompile interp.c ?^decompile(e, priority)$? editv interp.c ?^editv (row, col) {$? efree interp.c ?^efree (e)$? erasedb sc.c ?^erasedb () {$? error sc.c ?^error (fmt,a,b,c,d,e) {$? eval interp.c ?^double eval(e)$? help lex.c ?^help () {$? label interp.c ?^label (v, s, flushdir)$? let interp.c ?^let (v, e)$? lookat sc.c ?^struct ent *lookat(row,col){$? new interp.c ?^struct enode *new(op,a1,a2)$? opencol sc.c ?^opencol (cs) {$? openrow sc.c ?^openrow (rs) {$? printfile interp.c ?^printfile (fname) {$? readfile sc.c ?^readfile (fname)$? update sc.c ?^update () {$? writefile sc.c ?^writefile (fname)$? yyerror sc.c ?^yyerror (err)$? yylex lex.c ?^yylex () {$? DnDn@ Dn#@ Dn)@ Dn.@DzzDDDDDDDDD5sc.cint:t1=r1;-2147483648;2147483647;char:t2=r2;0;127;long:t3=r1;-2147483648;2147483647;short:t4=r1;-32768;32767;unsigned char:t5=r1;0;255;unsigned short:t6=r1;0;65535;unsig    y.tab.hscsrcx|ʄʔ0(xʴ0(-z-z 0(x` Czh" typedef union { long ival; double fval; struct ent *ent; struct enode *enode; char *sval; } YYSTYPE; extern YYSTYPE yylval; # define STRING 257 # define NUMBER 258 # define FNUMBER 259 # define WORD 260 # define S_FORMAT 261 # define S_LABEL 262 # define S_LEFTSTRING 263 # define S_RIGHTSTRING 264 # define S_GET 265 # define S_PUT 266 # define S_LET 267 # define S_WRITE 268 # define K_FIXED 269 # define K_R 270 # define K_C 271 priority)$? editv interp.c ?^editv (row, col) {$? efree i#F-@dd\g 2    scsrc/y.tab.hscsrcy.tab.hy.tab.h kmsuwn*8DT\bbblllz"<LLLZdt&.<BN^n~"0DVfx .<N^n.6FTbp~$0>Lbp coq @ D L њ@ (1 xxx|8xx LjH$$3ppxBA""" @0 2` "@(*IA(@D@"!D$"HH$D2BA""!  @ B??@((JB((@LH$HH$RB""!A8@ 8O$,4D"BxBd!"$@$2 BHxRǐ%RIxB"@!T&DDȑ(H2LD"BA"$_H € @|RHH&IBA@@A@"DDH0H"DDP$B"$@ $P @`MH$HH$D)BB @ "|DH(H"DDP! "$@* $ @   @ HD$"J$$(B A"@DH$H"DD D@Bp"$@ @ xxxx xp OHIptx<AOJVdt c $<1```0c>c͂È 3 < <<><~<< 6 >||6a<0`́3```3 0͂f afff<0fff18͍66 cf͘6a0a0` 0?o͏ a f<,0` fff0c2r8͍6 cf3130`c8ϟ|͙ǟ|ٱ6lo0c0`c3f7Ðʆ f l|| `0ĺ66 vc|x1! 00e<̓73f6lٳaa 0a`c3 f0`-f 0f~ff0`|͍66ͱvc`1 00al̓63fͱ6lٳ`sႆ0`0`c3 f0 `M0f `f ff0fffl͍v6͙vc`͘03 00al͛6f3f͙6lٳa3 Ì 0`c3 f0 G0< ~< <<0<`|D3 ?0a>f͍6gaώ a0a 0`  00a0`3 003<3 Sans-Serif10b WWkmuwn Sans-Serif10i ~,:H^flllxxx .>Nn~~~(0<HTfn|"28@N\jx $:DRhz$:Pl ,<LXhz&8H^p ct H@ x"`|0 H!H!4" Ј0! @   :~=s;88?hsw98` !"@D" `"h  "!"!!! a!"D"! @P  EB" !C"4 !!E !!#D"!<x" BP A! <!" $L D!!E @ 1(B`phql 61|!1< D" A @ !" !"@DA GE 0  0*C!d2 HDDDDBD!I<  D"')@@ !!@A D!!)  I?1  B!D"!@DBH8"F<@ D" Q"@ !"!!  D!) P(  B!D"!0B$!<D D" Q!@ ?!!@v! !)P! P D  !D"!B( !<D D"  !@  ""!&!!!0 a ` @1!D" HDD!<8pp ` @ > "s<~>s908<> Aplqsw 0Ca|!< @~ !< (P!<` `800<Serif12WW J,<L`hppp~~~*>N`4LT`l"2BRbjr "6Jbz0DVj0DL\n~,<N^lz 0< c@ " 0c3<r>r@|l w& <;66> 0  00??<Ǟ~6?3 & 81Fa A`13!F!`0  h `x`f6, 3&0!33 6#H8Fa p0c33!CA``x ` `xxf6 H 3><33 D(Ca qab0c33 A@ ``0pxlxvlw߆`xfaa8 3?2 33 HHL Yar0c3> @ށ`0c1 ;٘if#`fx0faa$ 3 &3HLCaZa:0c6ց`0`028c1 31af#;8x`faa(3&33 M|a Ja0c3ׂ`0`00c 31`cA axlfaa6H 3c?!33 &Fa Na0c3s`b`0a 31`qcA `xdfaa6 0?fr33 Fa qDa1c``` 0 c31a1`x8xx0 0 << 301??<y׃|c` xvx9wlq1`x 0`0 `xP @`0 <`xp |xSerif12bWW  .@Pjr||| ,BXj|(:Thp.>N^n~  4H\p 4FXl,>FVdr&4DP\hz& c@  q<  d d l DdD >0`0ノ88>99q@ `#)A8 D)AB"""@ 0DccAAb"$DBB!@@ ! B!! I!!B""  "BFPDBAb B"$HB B @  ?A$"0X$B!PDA !! D"  8 |X0blǃ6&3c< "@!!! @ɅB$DB!G""@G H@ T DH$dB3#""D$E"U!D0D@!! "'`Ip BD$D  D! <@E  H @ DQ!"DD C""$"H Abc @@!!" $Q ?DD4  a   @  P @  @HP"$D ""$$PB!" H@ B BD@DQ@  D D>M  "!$2@@! P P"8 8@DDD$Q  DD B$BDP  @HBȈ D0F @!"!4!2A@#DA `! (& @HDTTDHhD 88 BBC`` @08|ppp 8B 0G;x~xs9@k `s  1FDdc px  !@@@P0<@@P@``0x`8pSerif12iWWRh ".8JPXXXbbbn,888DLXdnt~ (4@LXdp| *<L\n ,<Nbz ,6DT\drz 0>LR`p| c D( @@A b@7 #0 s88;xxkwwws  0`0L@"""*IA$I"!$ $`2 B"1DDI"""$$   !x(JBD"@$D@NB !"B$QIEDA"!A@D!Ŏ4s1%Ƽ|!x@@"""$2 BDĄpCDB B8QIEx`AD@@#&QL "H)DDID!2x@@"""$   @$HDDB !"B,)yPAD@%OPD "H(DDI(!LxP@@""" $` @ 'H@ B&)AHA(A@!$PD"H($D(*( xQ@@"""H* $H @0 E HL#M" J#@DA( $!$QD"H)%D(6D!x@H<ð @ x0D`\wq9;xxq!ӎ:s;vƹ:"6!x !x    `!x 0xSerif10WWt$2@T\dddppp|&4@\jjjx *8HP^ft,:H\n~ 8L^n(4BN^nv *:FTbpz$0 c@h 8f =l< </8 0` 9Ɍ<;~v $>   8p1ǎ au:{=8x>yww<@8 7s8`c `1 $j)Ca\q6b`bbf1`qfb0#F$f 0   ?} x*Ab s6f0`d̈́hh1`yœ ͆fp0A@ x@xsc?ß~wn fc c1 H<200| 06f`0(xx?`Zœ ͆|<0A ٳ 3Ccf͛6 Fdh0 ?fc c1 Hǰ00| `0(̀hh1`Z h0 0 3cf͛0 h0a3c c1M00 0f0`)̀b`1bL lF0 0@ ك 3cf͛0s 8p@c c1 j L00 d2f,fb`f1bLqff9& 0 ٓ 3ccf͛03Mxqs | 00|3Æ8f y<{px\< |珝7wwsx! `0 0  `    <s8Serif10bWWp&4BZ`jjjvvv *8P\\\hr &4DLX^lx ,FVfv (>Pbt(8FX^lx .:FR\ht c "4A#X @@pDE@`F1L^flllxxx .>Nn(0:DRdl| 2DJR`n|,@FTfv2F`v.>JZjpx .DRdr cf !0 fH #2dBdH @bax<x~@H x? HB y0$ AB"<H @$!"D@"AA@ b @ HB A@@$ @@"0 A! !ADA"" !@ @ "  @@@@ @ G d@A@A#p"  $@ @    @  @B p840$If.L`hrrr~~~&8HVv,BJVbp"4FXjrz ,<Pbhv ,>Pl~ *:JVfv| (:R`p~ c  t c0 6ff |c`̀f|8pp*Àa ?0`>?  >`|00gf |f1`flq0f0`1 63`ٌc160  0` 0`00a1 `fm1 c<01f03<nj6` =l60 g100 x0`00a|o>`f9P3* `` ,~0 f31`3fnj` =l7 g0 00 `sߘٛ~>~?|l6#f0af1``0pc  ``08lc?330cfď` mo g0`x0 vf66633ccccml6#f 0a0f1o`0< ``` c1 c0fl` m0l0 /`00 0f6633ccccafcv 00ogo؍>030 00 3c>~?`၌f0a`0 `0a0 `0a0 >|`pg Sans-Serif12bWW      &"2BRfpxxx.@Rd  <R\jx 2DVhz 2FXl$8J`t0:JZj|(8FTbr c      a@̆d2@  H>  08 80>xAx>HD 8@AaB! HI ""C pD"@!D0 Pb!AF !0HD$ @@ @@@!@!@" BBAFP A E ! DH"(B @@@@@? ?"C"@@    I@ "ABA@H" B( 0x9b㏐#@@C !B  x8@ 8!A@@ #BB@O BI@* ā 3D#$ @  ! B  8I| 0"!A| @< "D|@H  I   %!B @g  !B D @BB "A "A(@@H  @@     "!% `!!"@B"A" @!B@  DDB)DD@A    !$H!)AAA"!"@B"@$ `A"" @@@ DD"1a #D@A  B 1  "$$$$$H#)B!B"@B"@px Ap@?x?C#1`C@>  B  "$#1  @@ @@ 0@ `@ Axx@  Sans-Serif12iWW RhSerif10 #tSerif10b 'pSerif10i + ~Serif12 / JSerif12b 3 Serif12ikm 7uwnSans-Serif10{} ;p Sans-Serif10bkm ?uwn Sans-Serif10i C |Sans-Serif12  G  ~ Sans-Serif12b   K   & Sans-Serif12i,0` P@p0` P@p0` P Q S U W Y [ ] _ a c e g i k m o q s u w y00``  PP@@pp00``#aAЂBvux  Ye M _   -#C3 ) eA`a҂ ӂ Ԃ u EgFGfdb‚x(q S9TextList #!Avvu| #!;| list +\ 9initialization9line access_{a clippingRectangle compositionRectangle destinationFormrulemask marginTabsLevelfirstIndentrestIndentrightIndentlineslastLineoutputMedium  kS s9composition 9character location9selecting 9tabs and margins9indicating9utilities&.26:LPZnrx~X[C[1]'_ %+)35igsa}qk=omu M;Ac ?{ewy{/} }  1!!!  =3  M  9labels:lines:selectors:9confirm 9labels:selectors:   #d+ pk|z 9setSelectors:#  B$sv|q 9ActionMenu9withCRs confirm\abort #B ps`| !!!9confirmation M! !  9selectorAt:! !#!|#!gx(!selectors!!!!! 9action symbols! !#!%!'!)!+!-!/labelStringfontlineArrayframeformmarkerselection!3!5!=!?  !7!9 !;s 9basic control sequence 9marker adjustment9controlling  *. 1/OOaWSc_UQY]?[ {[file in file out recover last changes display system changes do all remove all restore all spawn all forget do it remove it restore it spawn it check conflicts check with systemq!I!K9ChangeListYellowButtonMenu 1!Ci!E!M!_!e9!O!Q!S!Y@fn !U!W c![ !]  c!a!c 4@<D"D"D"D"D"@D "D@ "D@"D@"D@<0YÇXÇb$H"`" DI B$"@#HC>@ D$DHBH @ D$DHA@Ӄ#G84XrvÇLd"I DI DD a!"I#HDDD>I$DHDDD I$DH" #"#?5ҨAx@!#p|"# ##/#3pЇpчx#K  #!"#?Aɇx!#W#YreadFdnwriteFdn#]#_#c#e 8z #a 9fdn management e#5#7#/#3#9#1 9fork:withArgs:then:q#k#m9Subtask #o&q&&#k' =E#q&a#m$M #######Ye#g#s#u#w#y#{#}#9fork:withArgs:standardIn:standardOut:standardError:9initializeBrokenPipeCatch9terminateAll 9initializeEnvironment 9fork:withArgs: 9copyEnvironment9terminate:9fork:withArgs:withEnv:then:9fork:then:9initializeWaitManagement9waitUpdate 9markAndSignalAll 9currentEnvironment"######$Y&;&=&?&C&W&Y&[&]&_#e##plb|79program:args:initBlock:9environment: #B#gpA`|z# k#"#4E# q @̂C$AuȤ qAևpׇs}Ix+q## 9ChildWaitSemaphore'### ##RJ##*&# _###mq"7"9,### #C ####### Ai۬.hjEuȤ FvȤkuȤ}ِs}}xq##9ScheduledSubtasksAccesssProtect'q## 9ScheduledSubtasks  9criticalSection: 9terminatedWith: 9signalWaitSemaphore9taskId # ####"#AuȤCҁ@}vȤiԇuȤ'}}ˇxז9nonexistent#(#k M$W@!hC҉vȤ i'C}ˇ|q##9Environment#{.$?$$E$ $K#$$Q#$#$#$!#$'#$-#$3#$9#q##9CJOYRIGHTFq##9arrowclear q##9joyleftq##9f7 q##9joydownq##9TERM4404q##9F6Hq##9SHELL/bin/shellq#$9CJOYUPq$$9PATH .:/bin:/tek:/etc:q$ $ 9CJOYDOWNq$$9HOME/publicq$$9CJOYLEFTBq$$9f5q$#$%9f6Dq$)$+9F5q$/$19joyrightq$5$79BREAKq$;$=9f1remote q$A$C9TERMCAP/etc/termcapq$G$I9joyupq$M$O9f8q$S$U9PROMPT++ =##?##e#y#i$[$]#u"@p҇pӇEԇGևp؇A*ɇx99releaseExternalReferencesq$_$a9PipeStream $c$$ %&'&-$_&9 =$e$$aM $me$g$i$k$[9numberOfExternalReferences9openOnFdn:9openOn:$o$y${$$ ##?$q$s@B̂xEq"7"9q$u$w 9OpenPipeStreams #$s@|*D #!$}Up|C 9initializeOn: #!$}Up|nC#$sAЉvȤh}ˇxD$$$$ 9external references $k$i$g$[e $$$$$$M $A $$$$$$$$$$$$$w 9wordPosition: 9nextSignedInteger 9nextStringPut:9padTo:9nextString9skipWords: 9nextNumber:put:9nextNumber: 9padToNextWord9wordPosition 9padToNextWordPut:9padTo:put: 9resetContents"$$$$$$$$$$$$$$$$#!p !ćp!ć|Ǝ#?phsƘzpisƘz!а| #!$pwx9position:# ?$$ pŘzphpŘz#pа@$!||Ӊ9highBit## 1A!pĤ p !ćp ćvȤjp}ˇ|Ќ#!GpЇx=# gkpj  !pðjBhvvȤkp}|2 #!'pwx0#D$$A$jp# pusvpĤ"wGrpvvȤ kpv}xm9digitLength number too bigq$ 9SmallInteger$## 3wuiuȤ !pðA}|BivvȤ jvp}|3 #$Иzp|9even#pw|W #!$И{p|##BGpЇx˂#uaubx##EivvȤjp}|}$a$$$$$$$9nonhomogeneous positioning9nonhomogeneous accessing9positioning w$$$$$$$$$$$$ A$ 9ExternalStream{DM"$$'")$"1$s$u$$$ 9contentsOfEntireFile9isValid9isBinary9isTextB$%%%%% % % %%%%%%%!%%#!pЇx9#pЇx8#!pЇx9#pЇxe9#pЇx9#"1 ex8B#!pЇx8 #%"$qB|>9fileSize# exPB# $s# "g$qApuȤxD҇sdubx/?#p|B#p|f:P# %%g W$ "$q# pҨp!|pՙDCk&hH&gjɇinvvȤ I}uCH&gjɇio͂HvvȤ I}vvȤ I}n|:PipeStream is not opened for reading9isReadable#pu|@#%#"#?# @hBi|^Aq%%%' 9TekFileStatus %)%;`%%% =E%+%3%'M%-%/ #'%1p! |Kq%)%5%7%9$M%W%A%C%E%G%I%K%M%%O%Q%S%U%=%?9fdn9userId 9permissionsString9lastModified9mode9modeString 9longDescription9permissions9longAt:9links9deviceNumber9isDirectory9description"%Y%c%e%g%q%u%w%y%{%}%%%%%+#%K%[%]%o%_%api"h#vȤ,jv$vjv&vjv's}ˇ| ------)) ##%MAp#@| #p !| #%E%io%k%m%oph#v!|%v$|wv&|'|gdcb #%%s%G%A%O%?%Cp#p#p#p#p#p#| #p !| #! p pv|: #%M p!|P #p !|s#pv| #o%Ep"v|#%C%%%%php$v%w&| bytes   #!%=%QpѶpҶ|#pw| # p |%%%%)|"s%U%Q%=%%S%C%O%I%E%G%K%A%?%M #"1 Ƙyzs@ #A$p|@}%% %$a%%%% =$c%%%M%%%%$M%%$}%%%q%$uw%%% 9initializeOnFdn:9fill9next:into:9pad:from:to:9doAvailable: 9contentsEmpty 9nextAvailable 9dataAvailable"%%%%%%%%%%%%%%%#pŐr{v|- #wpp°|t1#!#5k$srfdBpuax$ #A%pЙqpu|/3 #A%p|3 #!k$srfdApubx%# g W$"m$qpҙA@hpi`uu|Dbuax4#!pЇx.2$#D A%uj/pŬ pvb|kvBv|/M# g W$ "m$q A%cpҙA@j#hEnou"mvvvkvCu/EnlH@ڳp)|mvvvvkqf|&File too large to read entire contents. #%yp|2#"g W$%pҙA@ip|-#e/g|B@uʐukvȤl}|6#!%p|4 #%zpЇ|a4%foundEnd%%%es$}%$w%%qu%%%%% 9PipeReadStream %$a% &&% =$c%%%M%%%%$M% $#$%q"1%w{$}"%%&&&&& & &&&&&#p|!I#pЇxL# exxM#"pбivuȤpBu}|F#!pЇxL#CpбjvuȤp}|G #!k$sdApubx|N#$g W$"$q& # pҙA@kvivDvcjɇv׷p&||I Pipe write error#"1 ex`M#Bp|lI#!p|AI## "$q&# jA`iɇԷp#|xiK Pipe write error #!#7k$sdBpubxM&&!&#$&e9modes$$w%q{ #"1$}% 9PipeWriteStream&)&+ fileDescriptormode&/&1&5&7 px$&3& 9opening-closing  "$$")'$s$u$$$"1{$s$q# k# #AЂBuȤD́}x#de#pkb|(# ###9#1 &AppщuȤ uvw}|Cq#o)# k&E"A# E&U / q@̂C$AɇuȤqAևC$AɇuȤp(}J凣s}Jxq&G&I 9BrokenPipeSemaphore'&K&K&M &I&O^T&S&I*&&Q _&M&C#mBroken Pipe# ####iAuȤCҁ@}vȤiE}ˇxϘ ##"#?@!Cx  #B#gpuȤs}`|##A|#!  ##ЇBuȤ DuȤs}}xP&c&m&o&e&g&i&k9environments 9task management9broken pipes9installation  ##{#s#g#e#}##y####w##uYDM6&&&  &&&##&&####"e&s&u&w&y&{&}&9taskId:9waitOn9start9initBlock:9absoluteWait9environment9interrupt:9status9initBlock 9enhancedPriority9isTerminated9kill9program 9abnormalTerminationB&&&&&&&&&&&&&&&&&&&&&&&&&&&#7z#w#!&q2u#p!xxUnacceptable priority value##"#&# "##Fp(Ԭ puȤp#} puȤp"}xl 9terminationSignaled#x#uxt#q&&&!"#|~9terminated 9terminatedWithCode 9terminatedWithSignal##"#&# "## Fp(Ԭ puȤp#} puȤp"}x%#cbcex*#"&q/5k M&3LD&d׉vȤ i+}ˤDp!|uIncorrect format for subtask environment=#y #q&&!"|x} #! uȤ}|#! &&&uug |"u!|$u#|x{# Їx#T{#p| ##ApuȤs}x t#!|z# k###iAf pDxYs#!|{$##&#&&"puȤp"}xpuȤ%}p$|puȤp%} ׇxjAlready waiting on this task9waitedOn@#("O#"Y#?"a5" &&"&s# # k##"&Ah՞CACbAɇɇpלAɇJهݨ Cuɇps{pPppuȤp32}1x,9closeExternalReferencesq&9FileStream9running#!|Xx7###&# #C ###### pkt=Biܬ.hjGuȤ HvȤmuȤ}ېs}}pӘxsx~#@u#!&/$#"&# "##Cp!Ip׬ puȤp&}x^Expected integer for interrupt &&&&&&&&&&taskIdstatusprogramargsenvironmentinitBlock accessProtecttermStatuspriority waitSemaphore&&''&B  !;&s 9critical accessing "0246e&&}#&&y &&"#&s#&&&{&&#&w &u## { #&E### Cannot execute q%%Error from system utility: 9copyUpTo:#"b"'p̈!sqsr|? 9displayOperation#"P"'p̈!sqsr|#""'p̈usqsr|_#!"V""p̈!qsr|e#"T"'p̈!sqsr|#"p""p̈!sqsr||#""'p̈vsqsr|#!":'!'p̈!srrs|09D0In:D0Out:D1In:D1Out:D2In:#"""p̈!sqsr|=#!"`"'p̈!rsr|,#d')v'+'1'35""p ͈"DvȤkD}ٜp( vȤkD}Ճsqsr|9operation:with:with:with:q'-'/ 9StringTerminator9asArrayMisuse of execve-environments should not be nil#"^"'p̈!sqsr|T#"R"'p̈!sqsr||#d"';'=# '?# p`k֬ p%|Ҙxчx49issueError 9isInterruptedWrite call returns incorrects number of bytes #C#'+'1""pw͈wBvȤjB}Ӄ`sqsr|b#!"n""p!rsr|# [g'+'G'ABu$x8$'I'K'M'O'Q'S'U'W'Y'[']'_'a'c'e'g'i'k'm'o'q's'u'w'y'{'}'''''''I/O errorSystem fault Data section overflow Not a directoryDevice full - no more available space Too many open filesBad file descriptor or mode File not foundMissing directory in file name Permission denied File already existsBad argument to a system callSeek errorCross-device link not permittedBlock special file requiredDevice busy File not mounted Bad device argument Too many arguments File is a directory File not binary Binary file too big Stack space overflow No children alive Too many active tasks Bad system callInterrupted system call No task found Not a tty type deviceWrite to broken pipe attempted Record lock error Text segment overflowIllegal operation in vforked taskMounted disk is dirty - diskrepair neededq''G 9ErrorMessages#" "'p̈!sqsr|#!"""p̈!rsr|z#""'p̈!sqsr|r#B #8'+""pw͈!C`srsr|K &#C'5"';"m'=# '# қp!|pƒcj٬³p(| ֜p|ԇxI)Invalid file descriptorRead call returns incorrects number of bytes #B'Z""pv͈!rsr|N 9operation:with:#B">'!'p̈!srr|` #!"cpɇx2*#" 3''!'"''" vvAAGըp$|p*ɇp+ɇpɇx|,/ Directory not emptyq'! 9FileDirectory/../.%#% 3'["C'' W" vvAADjp&lupJ|xD//bin/crdir#B'""puȤs}pɇpɇxw. 9valueIfError:#!"6'!'p̈!srqs|^#"T""p̈!srsr|Z #""# puiɇ|'#""'p̈!sqsr|#""'p̈!sqsr|2#! '*'+""pv͈!Csrsr|#B'""pv͈!rsr| #"f""p̈!sqsr|P#""'p̈!sqsr|#B #2'+""pw͈!C`srsr|"#""'"kpipuȤzy"#' |t8.bak#!" ""p̈!rsr|Z  #"""kpipɇ|4#"<'!'p̈!sqsqs|#!'R""pv͈!srsr|#" "'p̈!sqsr|#c#""pw͈!`qsr|V#B'\""pv͈!rsr| #!"gpɇx#!'4""pv͈!srsr|#"B""p̈!sqsq|#B #'+""pw͈!C`sqsr|#n |67#"""p̈!sqsq| #""# pviɇ|(#""'p̈!sqsr|#B #0'+""pw͈!C`srsr|#!"`""p̈!rsr|#B #$'+""pw͈!CC`srsr|Y#!"D""p̈!rsr| #"4"'p̈!sqsr| #C"pu`jɇx/#B'^""pv͈!rsr|= #""6# p!iɇ| #""piɇx#! '&'+""pv͈!Csrsr|#B 'h'+""pv͈!Crsr|#c#""pw͈!`qsr| #c')('+""p ͈"Dsrsr|#""'p̈!sqsr|#%#@|7#""'p̈!sqsr|#!'N""pv͈!srsr|##8 |7#!"8"'p̈!srr|#!" ""p̈!qsr|#!"F""p̈!rsr|a #""'p̈!sqsr|T#B #.'+""pw͈!C`srsr|#B""""p̈!qr|\#B #'+""pw͈!C`sqsr|#B'6""pv͈!rsr|  #"""pipɇ|;3#""'p̈!sqsr|,#"@""p̈!sqsr|B#c#""pw͈!`qsr|#""'p̈!sqsr|#">""p̈!sqsq|~|##C"U# # (93# k(;g? AhpiӇjkFlw'mn۬vH*قNvnqroL-͂KuL߬u|vLKH0قI*قJuqoߞu|NvLuqosNvLwnu21MvvTvTqxx> 9memoryLongAt:9oddb#I##g#i#1#3#/(?5&w!$k' $&u(A' W&_ @̂H@jBuȤvwԇՇԇ}ak٬ԇՇԇՇp(ԇԇM܉uȤOlmOnG} p3V4ZY| Cannot execute Error from system utility: #C"A# pjɇ|0 #!"pɇx", #""# pwiɇ|'# ' "C(KWp"CE|EE/bin/path(O(Q([(])( (S(U(W&e(Y 9display operations9system dependent operations 9portable operations9current working directory 4d""E"Q"I"e""""]"G"M"[""""W"S"q"{"""""i"""K"""""g"A"""""""a"Y" +""""""""""""k"""c""o"""""O"""""w"C"""3"}""m"u"y"""s"""_""""e"?"U"!DM*(o# # '#''!')';'='#C(a(c(e(g(i(k(m"""9errno9value9D1Out9errorString 9displayInvoke9operation9systemInvokeB(q(y({(}(((((((((((((((((# (sC(uCp!p|System call initialization errorq(w99Symbol##(i `x #capvpwx #Bapvx^# #?bcdefsgrx7#apvpwp x  #((gp"px System reports error: #(a6p!yz #!# pШ|y### ((g# pԨp"p{y System reports error: ##' u A´rA | # #?pЇx# #  #?pЇx#!ax #bcsdresfgx#(m `x (((((((((( operationTypeoperationD0InD0OutD1InD1OutD2InA0InA0Outerrno(((() ((((9execution 9set operation type 9set registers9errors $*'#')(i# (m(c'#C# (e(a(k"'""'!(g'=';{'+'#D !"'"{pjчpkԇԇx=#!!"5(#B|p|. #(p!|Can't write directories #!""5!Ap|Ɲ#%!!!(("w"5!pi֞p%|Hp|F exists9exists #!(!pp|? 9fileNamed:in:#"##!(!pvȤj}ip|ҫ 9newFileNamed:in:#B(x=9rename:#z) #!(!p|+9remove #!""5!Ap|#" k@hpvȤi}|t#"" !pvȤip}xܟ##!(!pvȤj}ip|ǧ#D ! !vȤk!}juʇxvʇpv|B#!!!!!@Ӝ@r@|pv&ps|# "15"3"5pЇчDp|H#)3!#|!|]/ #!) !p|y 9oldFileNamed:##OQ " sAB#ipvȤ js}pև|#&@| #!'!pqpr|##!)!pvȤj}ip| 9oldFileNamed:in:+#EOQg 1)@)sABjvȤlk'(ėsp%|}ˇup)||illegal character in file name file name empty)))'))0> )!)#)%s 9file accessing9file copying9alto file compatability  046< " s"!"'""%y!" !!!!"!""!"""" !"!"{ +stGxamples-Subtaking.st.bakxamples-Subtaking.stpipeTest.stEbugFixImage2coreipeReadStreamstdeltaDeltaipeWriteStrea.st ipeReadStreamcontentsOfEntreFile.stekSystemCallcass-createDirctory:.stixstforkFix.stPipeStream.stNchangedSourceOeltaT2.1.2.REDMEoxiesPipeBug.ailtaskFixes.stdelayfixes.st,bugFixImagebugFixChangesysCallUpdate.ttgoodiesdentitySet-fidElementOrNil.stdelta3.st.bakashMappedByChnges.steleaseCreatioChangeseleaseCreatioImageen-mandala:dimeter:.stdelta3.stJcloner.stubtask-absolueWait.sttestImageubtaskclass-trminateAll.stcloner.st.bakLcreenControllr-forkOSshell9ReadOnlyYou specified an illegal file name. #_#)5hx9listName#" )9);)=щvȤis}x9listSize9doThis:9hasRemoved:#!x#-!!)C"')E%pЇp"#vȤ hԇ}apׇxQtype name of file for reading9scanFile: #e!)Ippчxq)K! 9ChangeListController#-!!)O)Q%pЇp"#vȤh}apևx%type name of file for writing9fileOutOn:# -)U!%pЇBwpӇpԇx9recoverFile:# -)Y)[%pЇCpԇxH 9addChangeSet:9changes #-!%pЇpvp҇x# -!u%pЇч҇Ӈpԇx! #!wЇч҇x #-$k)e)pЇBxq)g)i 9ChangeListView )kQ(Q)g =)mQ)iM )q$k)o!o9openSwitches:topView:at:model:)sQaQQQ #$k)upAxq)w)y9ChangeList ){)Q3QM)w =)}))yM))))Mh))5)9);)=)E)Q)U)Ye!u!w!{!})))))))))))))!)!))))))!)))))!) 9removeCurrent9addDoIt: 9switchFilter:perform:9hasFilter: 9nextNonComment:9addChanges:9reportChangesOn:extension:9findLast:in: 9updateSelection: 9finishReportOn:9writeContender:on:oldText:9addFilter:9reportConflictsByClassWithExtension:9updateList9tabText:on:9listName:changes:removed: 9showingField: 9switchField:perform:9listIndex9filterCopy 9contents:notifying: 9changesAt:add:9changesAt:9equalWithoutComments:and:9checkSystem9checkWith:)))))PPPPPPPPPPPPPPPPPPPPPPPPPPPPQQQ Q Q QQQQQQQQQ!Q#Q%Q)Q+Q/ #)u ||Changes#| #!Їx#!u ´rr|#"))kP)AvȤi}uՁ$pևx9scanFile:do:q)) 9ChangeScanner )*;4{PP) =)4i4s) =E)*3*; M)e) 9isLiteralSymbol: ))*1 #))p|\9initScannerq)#d ))))k 1)))))))))***** Q* * *I*********!*#k*%*+A"#h%&)*+,-./0.123456789:;<=>?؀؀؀؀؀؀؀؀1/xˉ9xBinary9atAll:put:@9xDelimiter)r9xDigit))9xLetter)9doIt)D9xDoubleQuote)F9xLitQuote)H9xDollar9xSingleQuote 9leftParenthesis 9rightParenthesis9period9colon9semicolon9leftBracket)9rightBracket)9upArrow)9leftArrow9verticalBarq*'*)9EndChar)q*-*/9TypeTable))))))))))))))))))))))))))))))))))**))* * * ))))*)))))))))))**)))))))))))))))))))))))))))))))*)***!))))))))))))))))))))))))))))*#))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))I#$ 1*+*#*)))iuzvjuzAk#ƙq"ƛv|$ƬvjuzA$ƨzviy&Ƭ-v'juzAk&ƚq %ƙq#ƨzviyz*5*7*9e) )*=+4E4Y4e4g$M&*O*A)*** *C*EO*G*I*K*M)))))*?9scanToken9step9scanLitWord9scan:9scanLitVec 9scanFieldNames:9offEnd:9scanTokens:"*Q*S*W*c*g*k*m*o*q*u****++++ + #*%hbÁsƙ@c|}/#OQg@*A*K*U*%)ks[*?AB#hpԇpć(ƨGŐrp&|pԇsƞLp݇xUnmatched comment quote%#*A*?*C*Y*G*K*_)* *apЇpч)hpчՇ(Ɲap's$pҐs*ex*[*]*9word9keyword Unmatched parenthesis9literal #*A*epЇpd!ex9number(#*A*K*i*%spЇч%Ƭ %ƜpЇrqrpćDƚŐrp#|pЇd'ex; Unmatched string quote# ) 1)# hpЇddxz #!O*?ppчx(t #!*A`pЇpЇxs=#$OQ *?/ 1)*s*Cq*[*]*G* )* sAB#h0q/7.pԇݤ"+,p٤(ƞ'rpԇՁsćpԇdxx9-%#" *EO*w MQ*[*?)sA|pDFA'i* (ćpه|tq*y*{9ReadStream *}****y* =Y***{M**9on:from:to:* #c*Up`| **** Ym******$M$*KO *****#'")suw$9through:9upTo:9nextChunk9skipTo: 9positionError"******************#* prƛpАrpÇx9isSeparator #!`buapЇx #pŘ{phva|h"## OQEcsA#ipřqpÁBqԳćpŨć|ԑ#$ OQEcsA#ikpřqƙqpÁBć|##*OQgKs# jBC$hpՇpÁAsƨƬ pĒ|ć|)B #!pŨpyz#u|z#uaxI #*p!x#Attempt to set the position of a PositionableStream out of bounds #"pŘzpiyvazV #!$px#ax# v|# #*|}q** 9PositionableStream##EspivvȤjp}|##!*upЇxB}*{U***collectionpositionreadLimit****!$_s  $sw #**u$")'**KO*{ M*q* *** #*w{v| #!pЇx #d`Cbvuvax ****"sq*{#!p|#! *EO*w M*GpBpԇ|w#!pxƈ# OQgP*+AB#gDxcs#"1+(u*A[g 1) eBpd*(rGpdx} 9internCharacter:#*?pЇx~!#*e'*%+ *A eCŬ tCrrt"Edpևևx~q+ 99NumberK#"*% 1))*As"1q)**[*]*Їh$ƙq#ƬćbśAÁ-Ƭ e$,rpćipd*ƚdx0Ƭ pć/.dx9#*A 1)%a"ƜpЇvav&ppԁ|{})+ +*;+#(447+o =)+++M++++!DMH+c+%+'+)+++-+/+1+3+5+7+9+;+=+?+A+C+E+G+I+K+M+O+Q+S+U*K+W+Y+[+]+_+a 9startOfNextToken9abort9init:notifying:failBlock:9expected:9argumentName9matchToken:9parseArgsAndTemps:notifying: 9statements:innerBlock:9primitive9pasteTemp:9replaceEditSelectionWith: 9selectVariable: 9bareEndOfLastToken9makeNewSymbol:startingAt:9editor9temporaries9bindTemp:9assignment9expression9advance9parseMethodComment:setPattern: 9primaryExpression9initPattern:notifying:return:9cascade 9messagePart:repeat: 9blockExpression 9pattern:inContext:9addComment9notify:at: 9method:context:9parse:class:noPattern:context:notifying:ifFail:B+e+g+i+k+q+u+y+{+333333333333333333333444444#!+]p |#) !Ɵv| |#sƨЇshs|#c*E+K+mup  pчxq+o+9Parser#!)+]+s Ɯ v Ɯ v p# | expected#+++w*[+K "ƨp!|p|6 Argument name #!+K pЇyz*#C+}+Q+Csƙ |pvȤjwp}a|;i#GC*+%+[m++++I+++++k*3)3*A//,Q@jnsfrk "mpplp10Cp٨p+|pԇM̀pl!p٬ pԇpԇu ('s 5ƛp4| "ƙq 3ƙsp2|p50rmXpv9y  9encodeVariable:selfnil Expression to return9expr:encoder:sourceRange:q++9ReturnNode +,#3c33+ =+3W3[+ =E+,,#M+e+s#t++++ +++++++++++++++ ++++++ +0,,@, `,, ,vw"$&(*,.02468:<>߀ဢ〤倦瀨逪뀬퀮񀲂󀴂x4q+9LdInstTypeq+9LdTempTypeq+9LdLitTypeq+9LdLitIndTypeq+ 9SendType @q++9CodeBases @ @@ q++9CodeLimits @@ q+9LdSelfq+9LdTrueq+9LdFalseq+9LdNilq+9LdMinus1q+9LdInstLongq+9Storeq+9StorePopq+9ShortStoPq+9SendLongq+ 9LdSuperq+9Popq+9Dupq+ 9LdThisContextq+9EndMethodq+9EndRemoteq, 9Jmpq,09Bfpq, 9JmpLimitq, @9JmpLongq,`9SendPlusq,9Sendq, 9SendLimit,,,!e +,%,3G3K,e3UDM:,_,',),+,-,/,1,3,5,7,9,;,=,?,A,C,E,G,I,K,M,O,Q,S,U,W,Y,[,] 9printOn:indent: 9emitTrueBranch:pop:on: 9encodeSelector: 9sizeForEffect: 9emitBranch:pop:on:9emitJump:on:9emitShortOrLong:code:on: 9sizeShortOrLong:9isReturnSelf9canCascade 9emitForEffect:on: 9emitLongJump:on: 9isVariableReference9sizeJump:9printOn:indent:precedence:9sizeBranch: 9emitLong:code:on: 9canBeSpecialArgument9isArg 9sizeForReturn:9comment9comment: 9emitForReturn:on: 9isReturningIf 9printCommentOn:indent:9nextWordFrom:setCharacter:9printSingleComment:on:indent:9asReturnNodeB,a,g,k,m,q,s,u,w,y,,,,,,,,,,,,,,,,,,,, #B,cp xq,e,#9ParseNode#c,i,G, vpB#axё9pop:#!{ #!,opv| 9sizeForValue:#c,i,3,+vuCĕpBax' #B,3+upA`x#c,G ,vBrvėp!`x  #!,v@rv|w|#!{,{,',}!pu#x{}#zƌ#z#B,+,ipAćvx 9emitForValue:on: #B,G, pA`x#z܌ #!,5uu|p|9 #c,'pxk #!,5uv|p|y%#e ,klu"D !tD Cup% #ć#ćxA block compiles more than 1K bytes of code#zB#z #!,opv|#΋#!`x #B,+pAćx&#z #D),[sƘxv‰vȤkv"ćjpc"}s`x?!#DOQg WsAB#jŚqkEֶqEԶćʇ|8g#mO*w%MA,Y{w#WAkD҂HE&JIKm*nŨpvȤo}luIvȤ L簁I}ˇm(mI uȤI}އؤ,Ũm؇ImuȤI}ސs{xa #,+Ap|9expr:}21/-_2+,/92 ,,#,,1111 =+,,,M,,,,$M,,,,G,,,,,,,-,o,;9key:code:9reserve:9emitLong:on: 9name:key:code:9code:type: 9name:key:index:type:9size: 9key:index:type:9code",,,,,,,,,,,,,#Babx #!,,u pubx 9litIndex:2#D,@  /%ujC"# vj%C$ #vj#Cp"  k vBć&ćxb Sends should be handled in SelectorNode# #cabx2 #B /5++њ|CB|$| #,p`xu #!,op|> #c,,ppx #. #!u|k #!,p!v|w| #Bx; },-'-O ,,---#-% =,,,,M,,-- M- ,'-- -  9size:args:super: 9emit:args:on: 9emit:args:on:super: ----#B{x0#d,,,A,, @pԬ BC!rrv|Brp'b(B(k*)rw|!| #c- prxA#,i,+@ ,A٬ BH'rrB&Ĥ=!B!l$%rCwuć$ĤCvwućććx----!#<-q 9code generation- - -,'9SelectorNode{ -),-7-A-K-M =,-+-/-'M---1-3-5M-9,,'-;-?#B,+-="ēpAvxZ 9push:#Bx[ -C-E-G-I-q,,'9LiteralNode{ -Q,1 11-1 =,-S1w-OM-We-U9initialize2:-Y1eV#D-[3 ---1O] ++++++.e/k1]1_,>1a.-/+1c+--U@hA"͂CE&IJKLhIMNOh烄A0͂QRvV4vȤiV7}3XX94Z"͂[\=^^?4 p!x-q-]-_9Encoder -a,#-o1#1;-]1M =+-c-g-_M-e-i-k-mDMH--------------------+'--,+++E,-q-s-u-w-y-{-}-9autoBind:9encodeVariable:forStore: 9lookupInPools:ifFound: 9literals:nArgs:9name:key:class:type:set: 9encodeLiteral:9init:context:notifying:9undeclared:9sourceMap:9noteSourceRange:forNode: 9reallyBindTemp: 9associationForClass 9declareClassVar: 9declareCorrect:9declareTemp:9tempNames 9declareFailed: 9declareUndeclared:9supered 9declareGlobal:9maxTemp9noteSuper9newTemp: 9associationFor: 9nTemps:literals:class: 9cantStoreInto:9fillDict:with:mapping:to:9global:name:9initScopeAndLiteralTablesB------------------.%.'.).+// / / //////%/'/)/-1##-бwj ӉvȤ iE }|29pc#B x2 #"-pi|.#-p|K/#"--/--)[-#-Ҩp!iHp|4Capitalize globals or classVars9isUppercase 9addClassVarName:9changeClass:9classPoolC#( {/---d-+9+-ijӉvȤo}kvȤo}umvȤhDmFs}ˇ)p(|p/p|p*|5 9allVarNamesSelect: 9spellAgainst: Couldn't correctUndeclared Confirm correction to #!+7-p|[9#-,G҉vȤi}wȤkjԴ}hvȤi}|09isTemp#!+'pЇx]8#"ce---'-#iF B$%FspF|9 (  is Undeclared) q--9UndeclaredC{#0#"--/-#Ҩp!iEspE|~8Capitalize globals or classVars#-#qcxG&#!--+vbAvB`|- 9name:index:type:q--O9VariableNode#"#AuȤB|iA|.#cO*w$ebAfxb& #!'-A|7'q--9StdVariables{ ... ...q..self-O..q. . thisContext-O. . q..false-O..q..true-O..q..super-O. .q.!.#nil-O.!.!#O*w,AlvȤ mÃb}ˇx\!#+'sƨhpЇчz1 #B-y-+pAB|=#-.-.e3 OQ @AaBЂ CgD%͂GH)fx{%q./.19StdLiterals.3.U.Y.].a .5{.C.I.S =S.7.;.3M.9.=.?.AM.E+.G,#%  +IGIpjvlvipCsƚq ƜrvAvivlwp||*X .K.M.O.Qs+ 9LiteralDictionaryq.W-'q.[-'q._-'q.c-'q.g.i9StdSelectorsC{@...........k..y.}............o/.s....q.m,qq.q,qq.u.w9//,.uzq.{,q.,nq..9+,.`q..9value:,.qu.,uq..9@,.vq(c.,(cqy.,yq..9x,.q.,q.,q..9blockCopy:,.q..9*,.pq..9\\,.tq..9bitAnd:,.|q..9/,.rq.,lq..9bitOr:,.~q'.,'q..9bitShift:,.xq.,q.,q ., dq.,q ., hq ., jq ., fq..9y,.q*s/,*sb #!-y/+pAB|'q-#,#!-spr|b(#"sƨ ipЇz1#!/'-p!|p|,Name is already defined#sdx&#"/i#p"{ć|?*,More than 64 literals referenced. You must split or otherwise simplify this method##/-u-/-uȤpvȤj}p"p|i֨p%||B+Name already used in a Pool or GlobalName already used in this class&#C-u--9+A-uȤ*pvȤjp|ԬBԜp|pp}|(#C/!(u/#AvȤj|zu= 9hasInterned:ifTrue: 9scopeHas:ifTrue:#B ,-suq# p"pppps|~/#, -[uȤsm|| > #!-y/++pAB |t'q-K-'D#h-//--++E/1--{/3/50[ 3@deubrcpЇtmщvȤkCvEDbl}ˇsƨ)p&num׉vȤkpvEoJ+M.pl}ˇO0͂ x@" 9allInstVarNameshomeContext9receiver:selector:arguments:precedence:from:q/7/99MessageNode /;,#/00/71  =+/=//9M/?e/A#/C/U/[/k/q/w/}/ "$&x /E/G/I/K/M/O/Q/S9ifTrue:9ifFalse: 9ifTrue:ifFalse: 9ifFalse:ifTrue:9and:9or:9whileFalse:9whileTrue:q/W/Y 9MacroSelectors /E/G/I/K/M/O/Q/S /]/_/a/c/e/g/i/i 9transformIfTrue: 9transformIfFalse:9transformIfTrueIfFalse:9transformIfFalseIfTrue: 9transformAnd:9transformOr: 9transformWhile:q/m/o 9MacroTransformers /]/_/a/c/e/g/i/i /s/s/s/s/s/s/u/u 9emitIf:on:value: 9emitWhile:on:value:q/y/{ 9MacroEmitters /s/s/s/s/s/s/u/u //////// 9sizeIf:value: 9sizeWhile:value:q//9MacroSizers ///////////eDMB//, //////////,',--/3,9,;,C-,U/]/_/a/c/e/g/i,o/s/u/ 9cascadeReceiver 9checkBlock:as:from:9receiver:selector:arguments:precedence:from:sourceRange:9printKeywords:arguments:on:indent: 9printIfOn:indent:9precedence9receiver:arguments:precedence: 9transformBoolean:9store:from:9receiver:selector:arguments:precedence:B/////0000000000000000000000000000##G/,EG/S/_ vkwm#ƝpDwDnFfvu|ԕ 9sizeForEvaluatedEffect: 9sizeForEvaluatedValue:*#C,C- //wupFqu&svȤj}ˇCƃԁx q/.9NodeSuper#!=/kuzpAyudz #hsa| (#c/,I00/U00//қA|Aur%&G)|%&G(|g q//9BlockNode /,#/0o0/0 =+///M////DM2/,,'//-,IM///////////////,o,/9arguments:9isJust:9returns9isQuick9arguments:statements:returns:from:sourceEnd:9emitForEvaluatedValue:on:9emitForEvaluatedEffect:on: 9emitExceptLast:on: 9sizeExceptLast:9printArgumentsOn:indent:9printStatementsOn:indent:9isComplex 9numberOfArguments 9returnSelfIfNoOther9returnLast 9statements:returns:B/030507090;0=0C0E0G0I0K0M0O0Q0S0U0Y0_0a0c0e0g0k0m:#D+-=,- ,=//01/+/,i@ćvvcpFkvȤj}pvpܨKćvxK9initq//9ParseStack /0 00#/0/ =E/0/M0000 M 0 ,i/-=000000 #!0up!xE Parse stack underflow#!ax##uax#! #!ax00!positionlength0%0'0+0- 0)9results /,i-={ 9emitStorePop:on:#B //*v!ćpp$ćx #! ///,-3pћp|p| #!/,o3p|5 ##u| #[ 0?ABbAuarcx2q0A.#9NodeNil#!ax #!/zvƐr|" #,U3q| #,?/vАr|#k[ 0?G3 /gau uBCbcx#B/,3px#B /,;3/,i/pլ pv px#C,;vvvȤj}xP##,-uivvvȤ jᰁA}|#C I{G0Wu"vȤ j ć}ˇ$vx | U#F,W0?,73,',O0[sƨ pCjvՐr vvCv vCurvCsvvȤ=mlKƚs0)ćuss}x q0].9NodeSelf#v|#|Y# k0[3//pԨ AƨApӇx#,]3/pҨ qcx}*#"-{,+./-/0i,o,d"fpepը vepvȤ i氁}ˇvw|  9sizeForStorePop: #,/|2%#C [ 0? ,U/jrcvvԐr rjvv uABbAuapՇx 0q0s0u0w0y0{0}0argumentsstatementsreturnsnArgsNodesize remoteCopyNodesourceRangeendPC0000 -q,2/M/////,I////,///,-///,o/,'/{<-  of  must be a block or variable must be 0-argument block#-/3 /5pp| R#{0q///5y//I,CuЇxlnv‰vȤ`moIGJ)rG ܛ+rrw- vvHЇuHЇvwvnF}x 9keywords9#B//E[ //30?/M0/G/O0/IG p!C|I p(C|G p*C|L p+C|p-x q0.9NodeFalseq0.9NodeTrue#֚ #c ae@fcx #!/0pv!`|A argument#B0G0/3/50G#p!|E&|3 can't transform this message9tempAt:9tempAt:put:#//UGp`Bdbx~ #B ,C/G/+ sƨ`v%ppx #!/,-/5u pAr`|p"|F # %#//U,+-/,/0 /5p`Bdp GB( bEƚԐsxe 9macro #A/Aƙqu|; #B ,;/w/5upCru p@сx̃ #d {0,'0q   rk"p$x. ()#zV # /3/+$% ЛАrr|w #!_ //[0?/pAvCAEreyz #!_ //[0?/pACAErveyz #!/00pv"` pw!`r|ª False argTrue arg#! /IE/00pv$b pw#br bvwyz True argFalse arg#!_ //[0/pAvCAEreyzA #!_ //[0/pACAErveyzr #!/0/pp!`r|p receiver+#$//-,ou pAq`|CƚbCƃdjsƨjvȤ ikj}f|܎ L#g,;,,)/,/q/,i,1//5vlwnvkwm$pevڨp>uu|uu#u pe pcp@x` +#f/,),/G/S/,1+-=vkvlwm$ƞpbpapuGćvx܋ G#H,-q/0?//,A/_ ,-,o,E/5vjwlmup氁C#CFCGp |umuCIfuu|uwp| 0000000receiverselectorprecedencespecialargumentssizespc111 1   1-1qs 9expression types 9debugger temp access  ",B#//3/,9,U/,;,/s/u-,-,o//-////,',C// /e//_/c/]/a/g/i{ //k1/U/wq19ThenFlag4#', 1+;Y 111{;1y1(1!-=! BЇF()*eE+.102nup3|p5T|:9normaltemp\class var\global\undeclared\correct it\abort------ declare 9contractTo: as 1%1'1)1+1-1/1113151719scopeTablenTempssuperedrequestorclass literalStreamselectorSetlitIndSetlitSetsourceRangeslastTempPos1=1?1I1K:  1A+C0)1C1E1Gs9encoding 9error handling 9source mapping 9undeclared variables  ",04BH&--}-----{,++-s,-q+E------w--+'-----------u-y{1Q1S1U1W1Y1[selfthisContextsupernilfalsetrue 9specialSelectorSize 9specialSelectorAt:q.S.3!#!+1g0?1i01k01m0[1o1q1u/!#%')+x0niltruefalseselfthisContextq1s. 9NodeThisContextsuper1y1{1}e-U$M 111,,,I,,K,M1-,S,'0i-01,? 9sizeForStore:9isArg: 9emitStore:on:"1111111111111111 #!,pw|2*#!dx%#B ,+-=++%DCćvpAvxu'#ccabx%#+@|^+ #,cp`x% #-pЛqƐr|+#!++,M-A@rv|p"|) #B,+pAxH( #/++++uAж|$ A#A#$|EwEwFwv|+#B,S++-=+-CErA"Cćvp@x&#B{x*#!,10p#"rv|w|f*9noMask: #c,px4%!#B,++ +.,iu'BĤ$& B#$ēpAvx(#y-11nameisArg1111,Hl -q 1-,,,S,101,M10i,',I,K-,?{11keycode11112 -s ,,,,G,,;,,,,-,o,9LeafNode{ 1,#11122 =+111M1111 M 11,C,',,o 9receiver:messages: 11111#Babx8#cQ,' ćp"ćx#C,C,'u`v‰vȤj²#Đs}xͭ$#C,+-=+,i3vvvȤjBćvDćv}x«##,ovwivȤ jఁA}ˇ|11receivermessages1111T -q 1,,o,',C9CascadeNode{ 2,#22c2u272 =+2 2 2M2 222M2%22!2#-22229selector 9generateNoQuick9generate:9sourceMap 9decompileString 9generateIfQuick:#9selector:arguments:precedence:temporaries:block:encoder:primitive:2'2)23292;2C2E2I2]# OQgsAB#hp|> 5#",2+2-+21+++@/u uڐrr7iuxCB|EFGFB|(v()rB(|x9 9toReturnSelfq2/# 9CompiledMethod 9toReturnField:#25gabcdfxa3 q2729MethodNode#-|B R## O*w02{G,WW2=2?I2A/vpAjp҉vȤiՇ}ˇsƨ vpvهuv*vȤ i}ˇ+ćuv,䇈.vv|? |  #(uGA||< # 22G@vcp"|; #)2!2K-/-w2M->2O~2Q2-[$2S///2U2W2Y2[pvȤjv"vȤH"}p|oie*p(|C,p+|N0ur/ujR1nv3ṼmWvp8|"p:|vvȤ l[}\v"vȤH"}p|4 9cacheTempNames:Too many temporary variablesToo many literals referenced9newBytes:flags:nTemps:nStack:nLits:9initialPCCompiler stack discrepancyCompiler code size discrepancy 9literalAt:put: 9needsStack:encoder: #2_22a-p"h|%= 9numLiterals 2e2g2i2k2m2o2q2s selectorOrFalseprecedenceargumentsblockliteralsprimitiveencodertemporaries2w2y2{2}d -q  2#22!2222-{ 2,#22222 =+222M2222M2,C,,',-,o22,; 9variable:value: 9variable:value:from:22222222#c {2,'2"!p"$xu.() #B,1x,#B,'{2"wx- _ #!,o0i|, #!,o1|[-#Babx*#c//5B|abx+ #B,01x,22variablevalue2222T -q  22,;,,-,o,',C 9AssignmentNode{ 2,#2 3/3;3 =+222M2222$M$2222222222222222222 9codeThisContext 9codeSelector:code: 9codeAnyLiteral:9codeInst: 9codeAnyLitInd:9codeSuper 9codeAnySelector:9codeMethod:block:tempVars:primitive:class: 9codeAssignTo:value: 9codeArguments:block: 9codeBlock:returns: 9method:class:literals: 9codeConstants9codeTemp:9codeMessage:selector:arguments:9codeCascadedMessage:arguments: 9codeCascade:messages: 9codeEmptyBlock"22233333 333333!3%3'3)3-#1q@|$ #B,/A| $ #!,/++AuB`|#!--+AvB`|! #!,-G+AuC|G#/@|O$ #!,/+AuB`|)#23 3 2#25 ---[ 3psmәwҙ!vneEvvIg|!9isKeyword9isInfixq32 9DecompilerConstructor #B23A|Uq22#B/| #B//A| #c//3abcdx"9numArgs#a 0[000?k,/++BCDEFtwvȤ hJKv}|#! --3#+A#vE`|f$t#d G//53 3 kBՙwԙ#v|  #B2ps`|{ #B13+A|q21 #M/A|3133353739methodinstVarsnArgs literalValuestempVars3=3?3C3E2 3A9constructor$2222222222222222223Icomment3M3O3Q3S -1Aqs *,46:,O,Q,I,9,K,U,7,?,/,;,S,1,G,=,3,),E,-,M,A,5,+,W,',C,],Y,[C{N+,,, ,,,+0+0+++.-/+++0?+++++++0[++.e+++1q++-+M3Y3]3_3a$M3e,+,M,,S,],',-,o,7,?"3g3i3k3m3o3q3s3u3w3y3{3} #B,Sbx[ #c-apxcY#!,M|[#,|Z #B,SbxZ#Y#B*,',W ćxr\#!axOY #sƙ ||l[#!,M|\#0[@|)Z#,?|JZ33exprpc3333" -q ,+,],7,?,,S,-,M,o,'End of blockNothing more#) Ƭ v| ƞ | v|&#+/ ++33/ *e3 p!u|p#p#| hp(Frp$|p*p)||primitive:Integer>G#"+A3+9[gW33 3piu܀.r5܀vGݶp+⇀°vp++⇀°wvpEG()⇀°*x9selectAt: |  |  #"+A3;'3pi°±҇רՇxM 9replaceSelectionWith: 9selectionShowing#"+=3+A uvApЁAp±vx 9selectFrom:to: # vu|#M/!(u5+A3*[ 1Y 33{31(33! 333+'3;O*w0*I33 +93AvȤK|pԁBӚ| vJ q 'ƜpJ؇M/0D1354262kup87|9:ƚ|9ƬtA;mrƬ p<7psƛpn'9o!H#vȤ#L$2Is   _G}ˤ   _Gp(|pxtproceed as is\correct it\abort33+'9proceed9correct  is a new message  9correctMessage: Couldn't correct 9copyReplaceAll:with::#+A|#"+QpsvȤiv}`|i+#+=3*#m+E+K*[++3p#pЂ!|p#pԂ!|Eh )Ƭ p懣p#pԂ|p+|Vertical bar#!|'#+K3--s3,K++3+I23php"|qi֛p%|pЇp٨p(|Kjx Cannot store intoCannot store into argumentExpression#+G*!*[+O+S*+U "ƛ!ƐrpЇypӨzp'q %ƚpԇys#q*e*? ! " ‚ h   pӇ|#B+Qps`sƚA||nG#$++K*[+W*++3+I3* * -{*a*e/*s "ƞpy $ƞpчpӇy +Ƭpчpרp&|p*p(|y /ƚq .q -ƞpy 1ƛ.Ɛr pчpуyz expression right parenthesis#d +)O*w M+YpBuȤ{`pprsks|Z4#++3,9/[3+U3m*13+Ҩp!|hEip,!p(rp&|Ҩp)|ӇꇣNxS Cascading notCascade <- No special messagess#G+%+?+K3*[++3+O+U[ *#"1OQg@{m*]s//5kk 6ƛ8r8pjPQ2lSm 6ƬpӃ4p٨p(|pwq5pl8FF .ƙq -ƛwrpjplp٨p(|pvqLmwF %Ƭpjppl$mvF|Zp;ق^ylArgument#!+]p|.#m-q+-*++3A*#C*+34@hp% pᇣu ,p)ؐrp'|pqp,p.|xcVertical barPeriod or right bracket[#D6] 4[+44 4 +K*[+E+-*#"1OQg@{m*]s++4 sƞA'(v`|A"A%&`| +Ƭ Ap(v`| /ƙq .ƬpkApjAw`| 7Ƭ)QR3̓0kTj 7Ƭpڃ5p6A&`|p:9|9DoItIn:homeContext9DoIt Message pattern #,QCsកsfx8#B +]4+'sƬ sƛs|s "pԇx ->=#I+Y1+C+5+34//++4),Q252#pjwvȤHq}ˇpmnsfuplp%kבև *ƨp)|Lovw.|жNothing more # +)-}-[+_ +mpuȤ|`Bpapns|P #!+K ƛpЇyz 4!4#4%4'4)4+4-4/414345herehereTypehereMarkprevTokenprevMarkencoderrequestorparseNodefailBlocklastTempMark correctionDelta494;4A4CB 4=1 +C1C4?s 9public access 9code view interaction  $,.:@H&+a+1+M+-+G+W+S+I+U+_+Y+O+5+3+C+/+K+=+%+E+'+A+++]*K+7+9+;+[+)+Q+? 4G4I4K4M4O4Q4S4U4WsourcemarkhereCharaheadChartokentokenType currentCommentbuffertypeTable4[4]4a4c"V 4=14_1C 9multi-character scans "&)O*E*I*M*G*C*?*A)))*))** *K9Scanner{*+*%M4k4m #4o4qp|0 9initChangeScannerq)4u4w4y$M444444444)4o4}4 9nextChunkStream9scanClassExpression:do:9scanReorganizationClass:do:9nextSelector9scanChangedMessages:do: 9scanSpecialDo:9nextClass9scanClassDefinition:className:do:9scanMethodsClass:category:do: 9scanExpression:do:"4PKPMPQPWP]PiPkPmPoPqPs#DKs4}44=P% Ї jpkE ʇx# 9file:position:q449ClassReorganizationChange 4O P#P=PA4 =4PP4 =4PPO =4PPN; =E444M444 #B44p|vq44444 44N9OO?$M"44444))Q4244449category9className9fileName9classObject9parameters9fileOutOn:previous:next:9defaultName:9file"444444444N!N%N'N)N+N/N3N7#GpЇx0#c)QpxF)#$OQgd{W4sPAB#iFjp׉vȤkq+(|}ˇ|r ...#j#!)px #$*|#!4Wp҇҇x׷ 9nextChunkPut:#B`ax #44Apq| 9evaluate:logged:q449Compiler 45N N4N =E45 4M 4444444 9preferredParserClass9evaluate: 9evaluate:for:logged:9evaluate:for:notifying:logged:9evaluate:notifying:logged:444455 #B4ps`|#+m@| #!4psr`|O #c4ps|#55psuȤ{lB| 9evaluate:in:to:notifying:ifFail:9logChange: #c4ps|a5 555 9evaluating 444444M5!+A5555555+]9from:class:context:notifying:9translate:noPattern:ifFail: 9format:in:notifying: 9parse:in:notifying:9compile:in:notifying:ifFail:9format:noPattern:ifFail:5#5%5/51535557595;#?# !5'5525)5+445-14 4 4BЇsƙbppquȤ|em'nsƬ-o-BЇ|)o)BЇ|9receiver9addSelector:withMethod: 9removeSelectorSimply:#d+apuȤ|k|ϭ# O*w M/*DAbcax#d+apuȤ|k|̯#d552pspruȤ{ak|(#c55pspruȤs}a|#55pspra|$#B 15=5?5A!sBЇsƬFvge|v| 9insertAndSelect:at:9errorInClass:withCode:errorString:q5C5E9SyntaxError 5GMMM5CN  =E5IM5EM5M5K5?9flushMenus5O5#5Qsxq5S5U9TextMenu 5Wi5Y5[5g5m5s!again undo copy cut paste do it print it accept cancel proceed 95]5_5a!YL~X 5c5e c5i^5k ph<"x"""tx"p"xh"D"D"D"DDx8"DȈ D DP"D`8 @O$DDD$Da""" D> D Ӄ@8&D@"D@"D@"D@80 -@H @H@X4dH"LDH"DDH>DDH Dx<@@@ 5o5qx 5u5w5y5{5})55539again9undo 9copySelection9cut9paste9printIt9accept9cancel>#g 1555 5 5Xh55=/=1 MCBЇpEG։rdckI*+,hlO012uuvv3vmWw4Gփx,9setClass:code:processHandle: 9on:at:interrupted:q55 9ProcessHandle 55 555 =E555M555#c5kpBƚBѐs|F9process:controller:interrupted:resumeContext:5555M5 555555553 9resumeProcess 9proceedValue:9topContext9topContext:9interrupted:9proceedValue9interrupted55555555555 # sƨЇpчxY(#k' 55 ! 5 Ah҇I*ƨƨApۇ܇N݇x9method 9compiledMethodAt:9closeAndUnscheduleNoErase#!dx##!cx#!bx9## #`abcsdx #-=5pчxd #s`sascsdx55555processcontrollerinterrupted resumeContextproceedValue5555!d 5559access 9menu messages9control 555555535 9model:label:minimumSize:Syntax Error9on:aspect:change:menu:initialSelection:q559CodeView 56 M$MMM5 =5MmMw5 =566 M65 9on:aspect:change:menu:6 #5p|66 6 5 56"MUMWM_?$M66666Ye%37;59newText:9getText9accept:from: 9yellowButtonMenu"666#6)6+6-6/61676;MIMKMMMQMS #!6px9paragraph #B6!px 9deselectAndClip:#!666%6'sƜpA|ppԈՇևxM9scrollToTop9resetState#sƚ@|hsƚ@||#B==3sƛpЇzva|{ #̀sƘ{|= #?7pЇpчx*#63 C i _Q_65pШypبCEC'Ep+hpبCEC'E| 9textHasChanged&The text showing has been altered. Do you wish to discard those changes?# eU _69ppCxq6 #6=@|q6?6A 9TextController 6C69,9M=6? =6E996A =6G66M6Ke6I 9newParagraph:6M6Q6 #6Ia6Op"|.|#T6S6a+-6o6q6s66 6 6 166666666u6666666@́D%&(J+͂L.LPv1LRv3LTv5LVv7LXv9LZv;L\v=L^v?LvLvvȤ hLv}ˇvȤ hLv}ˇLvxq6Uue 9UndoSelectionzsq6cs 9CurrentSelectionagain undo copy cut paste accept cancel align fit q6u6w9TextEditorYellowButtonMenu 16oi6q6y6696{6}6!YX 66 c6T6a G DGDHDHI@@ ᣀd@$@$@$@yň@&D@$D$B$Cǁ < ,0 #"66pi| 9changeParagraph:q6E666e6I 6E6,7997;99M7 677766!#6%6'%!-779=e5u5w5y5{5}u556!366663366366666666666666666666666666666666 9processRedButton 9processYellowButton 9processBlueButton 9selectAndScroll9emphasisDefault:keyedTo: 9scrollRectangleHeight 9processMouseButtons 9selectionAsStream9readKeyboard9closeTypeIn9updateMarker 9processKeyboard 9processKeyset 9setEmphasisHere9displayAt:clippingBox:rule:mask:9select 9initializeSelection 9recomputeSelection 9reverseSelection9echo:9deselectWithEmphasisFlagSet 9noSelectionShowing9deselectWithoutDisplaying 9copySelection:9selectAndScrollFrom:to:9againOnce 9selectionIndex 9findAndSelect:7 7777777777!7#7'7)7+7-7/717375777=7A7C7E7G7I7K7O7Q7S7U7W7Y7[7]7_7a7c7e7g7s7w7y7{7}77777777777777777777777777777777777#7 h Ђ pi |rq6 #!6S6ax(#Bg6pЇ  vp҇xl"#u6S g36a6 Bhuzpԇ  B°GBpGp؇ys#61 б бpvҹ Ҹѱ| ## 16  u uu! ջ|uu! p׹ ո | #  v|o# 16 ѱ ѱ ԹpԸ |z&#$ /6pЇ ұui ְ ױujkuppڇx#y}# |#) #67%pЇpxq6# |+q #; ѱ|#(#! g 6pЇ  pԇx#! Aa[ӀЂ  u Ի ax3b#66pӚpҔpЇpчx#p ѱx(# 6 hBvsuua Ղ Ղpևr Ղx# %g 679p ԛqpӇsxjq7;6 9ParagraphEditor# !AC7?p|}q6# -679pчpӛ҂ x#"u 7 iuzp°vy$f#6%C6hpЇ BpӇx) #B9Css|~#= Їx8r #e!7Mppчxq6#66=7whpчp҇pӇ uȤp}֖pՙspԇpׇx,# 636S66pЇpчpCpԇpՇx\4 #6S6apЁx0#63666S6apЇpчpCpԇpՇGւxm1# 636a66pЇpчpCpԇpՇxw3#mu%Co66pЇ ч ҇ D ՇpևpׇxY2 # Ђx1,#-6S?6%C6%%pЇ тӇp  Gp؇pهx/#k%Cg 6pЇ ч C pևxK. #6s6pABx~{#!g6pЇ   ҂pӇxm #!6 wpćzOB#$* 67i 1 wU7k7oW63 M6 i%ׁCBupj KrJr j Ҷp݇{pPpv3pp݇y-= h*q7m)0q7q)> #! w{7uЇ"zCifFalse:m#%: w 5 )13s' gW 1k  CЇ ju U vƘ{ vkv vi  QƙqQƘ{lq vDCsktꇀ΀98{\{zT5#! 6S gsƛpЂ vq °x|#Ҁq #! wć{A5## w. 5 )1 + _C Їч"j iu 懀ڳxM ٻNkNkzT^#Bg6pЇ  vp҇xn #" w{7Ї"zeDifTrue: #! w5}ЇpчyPa#) 1 w  777363[g36BiӇpԇ lm'n(j)k ov´rvrrpHpvRԇpp3pԇp܇pOQ0pvԇp܇pOQ0pvRsyI([<{"')]>}"'*#" w kgЇҨчzv viv vՐrvi  {:$## w 6 7g AЇ٬i j&zpׇ v pґp҇y1N)]>}"'(#! w3s6g 6a6Їכp֤ pCԀՁ p؇  K± p܇y\ #! w5{ЇpчyPB #!6' pЇx-#! w{m]ЇDzB#6 66pЇpч h iqv wpՇpևxu%#pЇx'#8#(# ]6 h jӱiuձuiupvٸpڇxj6#BU7 7o 7 - 9 37k7B |D |F |H |J |K |L |p.xvq7)q7)unrecognized keyboardCharacter#1 а ӱ|w}# 6 6 6CњpЇӚp҇՚pԇx6$# **w M A v`|^p#OQg6S [gW + _ 1 q=6 1C3s6rnpЇBC$hsƟpՂ ׂ ـ  ް߱sƬ,v vRƐrqv u كs%v vRƚq  v췐rFo jXπ97qk]\rQ],  >k]ip"v mqƘxsƛrCs;l]rƛurvlurCs #p(&%ׂ p)x5Q#   6aCs   vԂ syz[u# [ph ӷpp҇x! #6 њpЇx# #7796A"x 9removeSelector: # x}#+C6pЇ BpӇx^* #6pЇx4j#6pЇxf #6pЇxa#g pЇ rxg# Aqs[ӀЂ  u Ի xiC#%" 5 )1 + 1k C  lu ㇀׳{Cj۲qڳ vBkiNm΀0Nm|>E# qs[Ӏ  u ӻ xc#rxg #AЂx6e}6A7 768.8a9999 =6E787M7e7#+-7778 8A"#%xSagain undo copy cut paste do it print it accept cancel q77 9CodeYellowButtonMenu 17i7x18ߛ again undo copy cut paste do it print it accept cancel  ## 77 c8T8a G DGDHDHI@@ ᣀd@$@$@$@yň@&D@$D$B$Cǁ < J #ЇxaK #!5= pxiQ #e8IpqxHq7 #!38'8Mp pчxFRq7#!c68Q8Sp sƨpxO 9displayContentsq7(#-58W6%8Y5Їp҇ppuȤp؇)|hKpp؇|L 9evaluatorClass9failedDoit#B33;8]6ppчp%pևxP # )8+C8Yph$pxhN }88c89 8e78s.88 =78g8k8cM8i8m8o8q M8{8u8w8y 9selectWithoutComp:9changeText:9viewToTop 8}8887#8u3;6sQܬ v ۃj6pЇ ӳ wp vpp vp؇pЇ xA #!g  тx6#!6'8u6%C pчp vpԇ Fpׇx #7QѨЇx8888+s8w8y8u9TextCollectorController 878.88 =7888M8888M858#=-5)%8њ|p҇ pppևx̺q88888t55 9ChangeController 879.999 =7888M8e8#+-88888A"#%xagain undo copy cut paste accept cancel enter q889ProjectYellowButtonMenu 1888888again undo copy cut paste accept cancel enter88888n*8DT\bbblllz"<LLLZdt&.<BN^n~"0DVfx .<N^n.6FTbp~$0>Lbp c88 @ D L њ@ (1 xxx|8xx LjH$$3ppxBA""" @0 2` "@(*IA(@D@"!D$"HH$D2BA""!  @ B??@((JB((@LH$HH$RB""!A8@ 8O$,4D"BxBd!"$@$2 BHxRǐ%RIxB"@!T&DDȑ(H2LD"BA"$_H € @|RHH&IBA@@A@"DDH0H"DDP$B"$@ $P @`MH$HH$D)BB @ "|DH(H"DDP! "$@* $ @   @ HD$"J$$(B A"@DH$H"DD D@Bp"$@ @ xxxx xp OHIptx<AO@D @C@ 88r 5u5w5y5{5}5589enterq889ProjectYellowButtonMessages 5u5w5y5{5}558999eM9 8!9 9 #8Ї҇x #88pABx9999!5s8! 9ProjectController{88 979-.9K9u9 =79!9%9M9#9'9)9+ M 9/5!6'- 91979=9A9G #59395pqxd 9setAction:q9 #99!9;Иzp|d 9actionTakenq9#6'g9?p vxJe q9#-99/w9C9EpѨxhHԇهxb 9selectActionq9 #99!9IИzp|Sd q9}9M 9O99].9k9i =99Q9U9MM9S9W9Y9[M9_%6-9a9c9e#g 6 p҇sx]#! w3s5Їը pCԀpև{6_ #-9gpxV^q9i9M9CRFillInTheBlankController9m9o9q9s !7%-69w9y9}9!79{5 9control defaults -!56'9FillInTheBlankController9isLockingOn9999&  9599s99lock access9model access9editing 9compiler access  e8%8#8'8!88)55)5c5=8+!3 9StringHolderController {87 9999999999paragraphstartBlockstopBlock beginTypeInBlockemphasisHereinitialText selectionShowingcurrentFontechoLocationechoForm9999p !79{k!9959 s9 9sensor access 9compiler accessing $.48JjS6e6'%-#!66%666666667655u655y5{u5}5w66666666666666666!667666666733673=766!3669{ 6a6S6s66} M9999M9596395=69wrappingBox:clippingBox: 9localMenuItem:9999999#=63-56%6=pқr|pӇpppЇpׇx~1#6! -3%9=#9isƟڇp -hu$jpppӇwppepؐsx6q6A#Bi3 p vx #pЀ|֝ #!9!|d 5{5}5y5u5w55#B33;96ppчp%pևx #}9 96A9,LM3? =6C999M9999M ::::9)59miniFormat9format9explain: : :LLL7#"O*w: Qg* A3;s6ApEhFGpiŨ!j٬؇ِۛrÇsćp܇ppx39copyWithout:?#(: =63:-!:353w;3%Bњp|pԛӇxhpևI؉uȤ+ipv p݇pnjsƚs p0pv2}px0 9selectedClass 9compilerClass+#"::::2LLL5= B׃phu +ޙ-,hpx-9explain:for:9class:selector:instance:context:methodText:q::9Explainer ::5 LL:L =E:!:-:M:#e:% # [gW:'ACx~q:):+9NewLine :/:1:3e$M:O:A:C:E:G:I:K:M:::7:9:;:=:?9explainInst:9explainTemp: 9explainNumber: 9explainMySel: 9explainClass: 9explainAnySel:9explainCtxt:9explainScan:9explainChar: 9explainPartSel: 9explainGlobal: 9explainDelimiter:":Q:_::::LyLLLLLLL$##:S:U:W:Y:[:':]Aiu{&$B"B'(I*|J9allClassesImplementing: is a message selector which is defined in many classes is a message selector which is defined in these classes "."Smalltalk browseAllImplementorsOf: #F#$.:a:c:e:g:i:k:m:o :q:s:u:w:y:{:}:::! i#"i%$isƘ{0#j-,C j)+C./i4 13i65i|2^:"is a constant. It is the only instance of class UndefinedObject. nil is the initial value of all variables."9nil5"is a constant. It is the only instance of class True and is the receiver of many control messages."9true5"is a constant. It is the only instance of class False and is the receiver of many control messages."9false 9withAllSubclasses one of these classes  or a subclass"is the receiver of this message; an instance of "9self&"is just like self. Messages to super are looked up in the superclass (9superclass)"9super2"is a context variable. It's value is always the MethodContext which is executing this method."9thisContext1#$  Wvjkvv|iBԶq BӶqBѶvjiBԶq BӶqBѶvk|Zx#"Z:::):*:Q:*::::*::*:::':I:*::/:%:::Wvi! |#"|%$|'&|*q)(|-q,+|0q/.|21|43|65|87|= :[9[9<9|?>||||'|*|,|{XL"Period marks the end of a Smalltalk statement. A period in the middle of a number means a decimal point. (The number is an instance of Float). A period in the middle of a selector means a compound selector. (To the left is the superclass, to the right is the selector).","The characters between two single quotes are made into an instance of class String"."Double quotes enclose a comment. Smalltalk ignores everything between double quotes."O"The characters following a hash mark are made into an instance of class Symbol. If parenthesis follow a hash mark, an instance of class Array is made.""Expressions enclosed in parenthesis are evaluated first"J"The code inside square brackets is an unevaluated block of code. It becomes an instance of BlockContext and is usually passed as an argument."_" means that this method is usually preformed directly by the virtual machine. If this method is primitive, its Smalltalk code is executed only when the primitive fails.")|)x1"Uparrow means return from this method. The value returned is the expression following the ^"V"Vertical bars enclose the names of the temporary variables used in this method. In a block, the vertical bar separates the argument names from the rest of the code.">"Left arrow means assignment. The value of the expression after the left arrow is stored into the variable before it."G"Semicolon means cascading. The message after the semicolon is sent to the same object which received the message before the semicolon."v"A colon at the end of a keyword means that an argument is expected to follow. Methods which take more than one argument have selectors with more than one keyword. (One keyword, ending with a colon, appears before each argument).iA colon before a variable name just inside a block means that the block takes an agrument. (When the block is evaluated, the argument will be assigned to the variable whose name appears after the colon)."/"The single character following a dollar sign is made into an instance of class Character" "A minus sign in front of a number means a negative number."#"An e in the middle of a number means that the exponent follows."c"An r in the middle of a bunch of digits is an instance of Integer expressed in a certain radix. The digits before the r denote the base and the digits after it express a number in that base." "the space Character" "the tab Character""the carriage return Character"w#(43I[ :5:G::C0:::::S:::::sƘ{!ƨ{CivȤoۉvȤj}uȤs}s}uȤs}Cs.l/F?ivȤoۉvȤj}uȤs}s}uȤs}Cs (p'|{,l-FQ0m65E32E7282229222|!s9messages<primitive:.2. To see the definitions, go to the message list pane and use yellowbug to select 'messages'.", which is the selector of this very method!7. To see the other definitions, go to the message list pane and use yellowbug to select 'implementors'." these classes many classes" is one part of the message selector  It is defined in ]#%6::4::'::/:Lo7LqkC;Ls Lu3LwAuȤ{kK#$&G()|-ƙ,|YƬ@NlAvȤ"ivȤj}uȤs}Rs10s}l#57ƒV8|#:8|g"is a global variable.  is a class in category ." Browser newOnClass: .q::9Behavior C:LILKLU:LmM;::'U8W:m:{:::::::::::::::;;;;; ; ; ;;;;;;;;;;!;#;%;';);+;-;/;1;3;5;7;9;;;=;?;A;C;E;G;I;K;M;O;Q;S;U;W;Y/#;[;];_;a;c//;e;g;i;k;m;o;q;s;u;w;y;{;};;;;;;;;;;;;;;;5+5-; 57-9showVariableMenu:collect:9instVarNames 9allAccessesTo:9allCallsOn: 9browseAllCallsOn:9someInstance9subclasses 9includesSelector: 9whichSelectorsAccess: 9recompile:from:9sourceCodeForMethod:at: 9allSubclasses 9sourceCodeAt: 9sourceCodeTemplate 9printHierarchy 9subclassDefinerClass 9compileAllFrom: 9browseAllAccessesTo: 9checkSuperAddSelector:9hasMultipleSuperclasses9updateInheritanceTables:9insertClass:selector:in: 9allDynamicSuperclasses9whichSelectorsReferTo:special:byte:9compoundSelectorsMatching:9dynamicMethodDescriptionAt: 9dynamicSuperclass9superMethodDescriptionAt:9removeFromInheritanceTables 9methodDescriptionAt: 9tryCopyingCodeFor: 9compileUnchecked: 9checkChangeSelector: 9checkMethodFor:9compileBroadcastCodeFor: 9poolHas:ifTrue:9copyMethods9recompile:9allSelectors9format:variable:words:pointers: 9allClassVarNames9basicNew: 9allSharedPools 9crossReference9superclass: 9kindOfSubclass9printMethodChunk:on:moveSource:toFile: 9methodDictionary:9decompile:9hasMethods9compile:notifying:trailer: 9allSuperclasses9isFixed9compile:notifying:trailer:ifFail:9allInstances9isPointers 9decompilerClass 9compileAllSubclasses 9subclassInstVarNames 9instanceCount 9allInstancesDo:9addSelectorUnchecked:withMethod: 9whichSelectorsReferTo:9compileAll 9allSubInstancesDo:9flushCache 9inheritsFrom:9isBits9selectorAtMethod:setClass:9removeSelectorUnchecked: 9sourceTextAt:9defaultSelectorForMethod:9obsolete 9allSubclassesDo: 9removeSubclass:9addSubclass:9whichClassIncludesSelector: 9allSuperclassesInto: 9sourceMethodAt:9superclasses 9conflictCodeFor:9printSubclassesOn:callingSuperclass:level:9removeFromInheritanceTable: 9unmovedVarsFrom:9updateInheritanceTable:oldSelf:9compileConflictCodeFor:9accumulateInstVarNames:traversedClasses:9selectors9removeClass:selector:in:9isWords 9withAllSuperclasses 9classVarNames9sharedPools 9canUnderstand:;;;;;;;;;;;;;;;;;GGGGGGGGGGGGGGGGHHHH!H'HHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHKKKKKKKKKKKKKKKKKKLLLL L LLLLL!L#L%L'L+L-L/L1L3L5L7L9L;L=L?LALCLELG#A#4@|% #  u|nD # :pЇx]]# ;5 :pћpu|p҇xY#4@| #:php|f#ie# :pЛpu|pчxP\ #4:p| #!{;!xI a descendent of #;Aiscphc|XEI#JOQg;k{1(Wm'+-sAB#kDlumunDop։vȤ-jnʉvȤI*ۇvE}}ݘ{tQP߂Hus|# ;k;phsƙui!|vvȤj%}|,inst.#$! s;::k;C4 @iC҉uȤ)ppvȤjvȤk- +s}}}| B#&; s;:;k;C4 @iBvȤk}jppvȤ?lgvȤm, *s}ˇgvȤm, *s}}ˇ|^9hasSpecialSelector:ifTrueSetByte: &##;G;;;:G/0E j#Aj!AGp)pۃf|ESenders of Users of 9openListBrowserOn:label:initialSelection:q;;9BrowserView ;FY,G; =;FQ;DM;;;;;;;;$k; 9openClassBrowserOn:9openListBrowserOn:label:9openMethodBrowserOn:withController: 9openCategoryBrowserOn: 9openMethodBrowserOn: 9openOn:withController: 9openProtocolBrowserOn:B;EEEFFF!F3FC<#f,eWc;O; MG/E5XE EEEEԞ@ч#|FlJؑmp,-kkuu01rnu1v3rxNobodyq;; 9MethodListBrowser ;=E}EE; =;EqEu; =E;= = M<5K;9newOnClass: <=#<<< I"( I"IxK "DI ":I;"8$"D$D$|$@$< <_@`ӛёbcxG(q=_=a 9SystemOrganization=c>>?=?? =e=q>> ==g=k=cM=i=m=oM ==s=u=w=y={=} 9superclassOrder: 9printOutCategory:on: 9fileOutCategory:on: 9fileOutCategory: 9printOutCategory: 9changeFromString:=>>>>>## ==s=pvȤjC}iE|e 9listAtCategoryNamed:q==9ChangeSet == >>= =E===M==s==>#' :{CwȤ^nmivkjvlҁAѝvkҁBѝvluȤҁE}uȤҁF}ҁAҁBmnƛմ}|d #e=p|cq====_=sDM>=)===============-========)Q==e9printOutClassChanges:on: 9printOutChangesFor:on: 9addSelector:class: 9changeSelector:class: 9removeSelector:class: 9fileOutChangesFor:on: 9commentClass: 9changedClasses9fileOutClassChanges:on: 9removeClassChanges:9removeClass:9classNamed: 9atSelector:class:put: 9atSelector:class:9removeSelectorChanges:class:9oldNameFor: 9reorganizeClass: 9renameClass:as:9addClass: 9changedMessageList9atClass:add: 9atClass:includes:9isNew: 9reorganizeSystem9printOutOn:B=======>>> >>>>>_>c>e>g>m>o>u>w>{>}>>>>>>>#!kx9Z#B,W={=;e=======,O,O==p,$ЇЇ*#'Їvx#p/Їp.Їp1 ЇЇp3ЇЇЇvp54Їx_ class initialize9add rename: #9rename9definition9change9printOutOrganizationOn:9reorganizeV#F.=kG(=W{===e=pAkAjԉuȤxvȤl'}ڨه,vȤmه/}ˇV543r 2هvx'O9printOutChangedMessages:on:  removeSelector: 9soleInstance initializeq==9Metaclass #B==p!`xCC#B====p#p!`xE#B =(===p$pp!`xFM#F*=kG(=W4>=>e=pAkAjԉuȤxvȤl'}ڨهvȤm-}ˇT321r 0هxBI9fileOutChangedMessages:on:  removeSelector:  initialize #!=,Op!x+<#k=@hщvȤip}ˇщvȤip}ˇ|:A#B$W)Q===4=> ===> >,O>=p#ЇЇp#|p*p(Їp,Їp/ srmЇp10ЇxZ rename: #9putCommentOnFile:numbered:moveSource:9organization 9fileOutOrganizationOn:'#!щuȤs}щuȤs}щuȤs}щuȤs}щuȤs}x>#"=====kpp|p%pAҁApx<$#$  >! "#r qiv!BriBDk||X class#e=>pxkuȤ Cl}xcWq>>! 9IdentityDictionary Q{>#>I>K>O>>]$M>)E>%>'+ky 9noCheckAdd:with:9removeDangerouslyKey:ifAbsent:">+>->/>1>3>5>7>9>;>=>?>A>C>E>G#BEE>p@xQ #!>%Gp| #  >pApax #C IpuȤ|jBp|F #C+IpjpsƬ v`ppӇ|' #>hapia|: #D IvpщvȤkƬ pBsƙs|s}|+ #C puȤ|j|k #B>'puȤ|x #"  IvpщvȤipsƚs Cp}xJ #C+pjpv`|N +#F +I Epjpsƚ|pssv`plvvjpsƨppkpx %#%  +IIpjvlvipCsƙqƨvAvivlwp|| #!Gpx #" IvpщvȤipsƙs}x }M>MvalueArray>Q>S>Y>[~P >U>Ws 9dictionary removing 9dictionary enumerating  ky+>%>'E{#B>aщuȤ"|uȤ"}|V9none#C %щuȤxjuȤs}ԜxG #!==p!x}:##>i3*M>kщvȤj$}iG|g^oldName: *q4e*; #!==p!x5B>#D=>q==_ %>sp$ p"p$GvȤ=kӉuȤs}Bsƨ ӉuȤs}Bsƚs *}ˇx?oldName:  class#!==щuȤs}p#xe9$#k MG>y('1@hvȤiɉvȤj's &}}|C #B k[=p҉uȤD|xU#B҉uȤz|{V#!===>ӝp!|p!|]9isMetaA#$ >=s===4>W*>=]pқp!DpvȤip}ˇvȤ j*}ˇۇ,ć-ۇO臈ۇۇvȤk}ˇxLWarning: no changes to file outSmalltalk removeClassNamed: # SystemOrganization#qcxBD#$">=s==={>W>=]pқp!DpvȤip}ˇ)vȤ j,}ˇ݇.݇Pꇈ݇݇vȤk}ˇvxRWarning: no changes to print outSmalltalk removeClassNamed: # SystemOrganizationG#kG>>>>>>A@hvȤiɉvȤ j%}}vȤiɉvȤk&%}}vȤ l%'}ˇ(ܬ )+|]6 -  remove Reorganize System SpecialDoIts - ()#AКАrАrѐrАr|d5#3@`@aAbrcBdxr4>>>>>classChanges methodChangesclassRemoves reorganizeSystemspecialDoIts>>>>b  >>_s 9change management 9method changes $,>!e=)-=============)Q===========#D =sW>=qkpvȤjrC чCćч}ˇxzd9newPage!#D =sW>>>qkpvȤjrC чCćчrud}ˇчxa9fileOutOn:moveSource:toFile: 9removeFromChanges#"!!>>=wA$ipևx,a9asFileName.st #"!!>>>W=uA$i&Hههpۇx)c.pp9timeStamp:*#" ")>W4>=]"'=)[=}>@sƨ@wiч҇Ӈ&IӇڇMۇp.xY_ 9readWriteShortenSystemOrganization changeFromString: q>=c 9SystemOrganizer>>>>(_ =}=y=w={=u=sThese categories are only intended as a guide. It is OK to put a class in several categories, and this will allow you to maintain a category (e.g. Current) for the classes with which you work most frequently. Observe the paren and quote form when editing system organization.)>>>>>>>>>????? ? ? ??????????!?#?%?'?)?+?-?/?1?3?5?7?9?; 9Numeric-Magnitudes 9Numeric-Numbers 9Collections-Abstract 9Collections-Unordered9Collections-Sequenceable 9Collections-Text 9Collections-Arrayed 9Collections-Streams 9Collections-Support 9Graphics-Primitives9Graphics-Display Objects 9Graphics-Paths 9Graphics-Views 9Graphics-Editors 9Graphics-Support 9Kernel-Objects 9Kernel-Classes 9Kernel-Methods 9Kernel-Processes 9Kernel-Support 9Interface-Framework 9Interface-Support 9Interface-Lists 9Interface-Text 9Interface-Menus9Interface-Prompt/Confirm 9Interface-Browser 9Interface-Inspector 9Interface-Debugger 9Interface-File Model 9Interface-Transcript 9Interface-Projects 9Interface-Changes 9System-Support 9System-Changes 9System-Compiler 9System-Releasing 9Files-Streams9OS-Interface)&08>HNVjv|&28@JNTZbn_?A?C?E5+ ?G$ ?IY5>y?K?Mi(w Y**y?OS?Qmo7 ?S?Ua a?W?YCI?[?]?_?a?c?e?g/ g5C?i?k?m?o?q?s:?u?w=?y?{2/?}????? #? m ????>???:?y?? ??5??7;9s6???? ??????/?????9i9?;;?????55C??8??9?8)w)K)g?QK ???)=?????4????2/24?3-]1.S-K/727,e+o/+4e-#-???$'&%$_&%##k%%#A9Magnitude9Fraction 9LargeNegativeInteger9Random 9SequenceableCollection9LinkedList 9MappedCollection9Stream9LookupKey 9DisplayMedium 9DisplayObject9InfiniteForm9OpaqueForm 9FormHolderView9FormView9BitEditor 9FormButtonCache9FormEditor 9FormMenuController9FormMenuView9WordArray9Boolean9False9Object9True 9UndefinedObject9Class 9ClassDescription9MetaclassForMultipleInheritance9BlockContext9ContextPart 9InstructionPrinter 9InstructionStream9Message 9MethodContext 9MethodDescription 9ProcessorScheduler 9ClassCategoryReader 9ClassOrganizer 9MethodDictionary9RemoteString 9ControlManager9NoController9View 9ScreenController9ListView9SelectionInListController9AlwaysAcceptCodeController 9CodeController9OnlyWhenSelectedCodeController9OnlyWhenSelectedCodeView9TextView9Workspace 9WorkspaceView 9BinaryChoiceView9BooleanView9Button9IndicatorOnSwitchController 9LockedSwitchController9OneOnSwitch9Switch 9SwitchController9SwitchView9BinaryChoice 9BinaryChoiceController9Browser 9ContextInspector 9DictionaryInspector9Inspector9Debugger 9NotifierController9FileList9FileModel 9TextCollectorView9Project9ProjectView9Benchmark9MessageTally 9SystemDictionary9Change9ClassChange 9ClassCommentChange 9ClassDefinitionChange 9ClassOtherChange 9ClassRelatedChange9MethodChange 9MethodDefinitionChange 9MethodOtherChange9OtherChange9Decompiler9Checker9SystemTracer 9TekSystemTracer#sƘ{@|@|!7 #=E=?psp"x@ 9classDefinition#!x5l#!=5=Eaћpspx.)#!=!3=C=?5bpp%pӛp"sx5 #!3fp!xh #!3=#dp!xcH#H #=>:sƘ{p|S#C@:=9p`jsƘzƨpyU9compile:classified:notifying:#!=@esƛsƐrxp!xRS 9methodDefinition# @@ @<<<sƜA"#|IsƬ A&'(dI|Jadd protocol<file out\print out\spawn\add protocol\rename\removep#(63I[ @!@#@%@'C0:S@)@+@-?:::@/@1@3@5@72ƬX!ƨ{C$kvȤmۉvȤn}uȤs}s}uȤs}Bs &'(D{Mi.i01|:Ƭ>pivȤmvȤo}uȤs}s}uȤ{ii6789|{Il(9subclass:instanceVariableNames:classVariableNames:poolDictionaries:category:" is one part of the message selector . these classes  It is defined in ." Smalltalk browseAllImplementorsOf: #"is an instance variable in class ."  browseAllAccessesTo: ''.9hierarchyG#B(=I?='@=}=U@;>:=@===#=!@?,Q,O=@7!Ɯp|#Ɯp|'Ƭ py/Ƭppڇpۇp-sy1ƬpՃ0p1sy3ƛzi9categories 9logOrganizationChange9protocols# @C<=W4"'@sƨ@wiч҇ӇӇՇxaq#! 3=Q=!=CpҨp!|cp!pp՛p$x|G #!32ep!xR#@=sƘ{)@hppvȤ iؙs}ˇ||N2 **Hierarchy** #@!|=?@7,O@? #!34bp!x6# @:sƘ{p|I#C @; A#ErvȤj}|b  then accept or CR #!m=3pЇxi? #@=3pЇx?9printOut #;;ApxF #;;=SApxF#=@7=!pШxp"psxOF#=?=!pШxp"psx'>#=,O=!pШxp"psx>#=@?=!pШxp"psx>#:::;;:pщvȤi}vȤh}h֬ Dpcx;&#::!-G;;:@pщvȤi}vȤh}h۬Gp*Ճfx9Users of #:#AAx39Z#4::>=O@@@@-/(=EeWc@=!@;A=5BB==9pШxp"p&hؘxrl,={,iNmPډuȤs}jU4RR1{¶%±9 7ƒV8rǁBRR1{wk:vkƒVhpƚs qlps{pjځ@=!= >p "pԀ%〦%#'p(xDXType destination protocol (Class>protocol will copy)>q?w@ A:@ BgBiBo?wM~A1@AAAAA A A >AAAA=AAAAAA!A#A%A'A)>A+A-A/@@=;=;?;M,O)Q,Q@i;s=u=y={>47>=@@=:===@@@@@@=&9subclassOf:oldClass:instanceVariableNames:variable:words:pointers:ifBad:9printOutCategoryChunk:on: 9printOutMessage:on:9printOutMethodChunk:on:9printOutMethodSelector:on: 9commentTemplate9validateFrom:in:instanceVariableNames:methods:9methodsFor: 9copyCategory:from:9copyAll:from:classified: 9copyAll:from:9fileOutCategory:on:moveSource:toFile: 9addInstVarName: 9removeInstVarName: 9copyAllCategoriesFrom:9copyCategory:from:classified: 9updateInstancesFrom:9copy:from: 9superclassesString9fileOutMessage:on:moveSource:toFile:9fileOutMessage:fileName: 9moveChangesTo: 9copy:from:classified:9fileOutChangedMessages:on:moveSource:toFile: 9printCategoryChunk:on: 9errorCategoryName 9classVariablesString9instanceVariablesString 9sharedPoolsString9whichCategoryIncludesSelector: 9compile:classified:A3A?AwAyA{A}AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABB B B BBBBB#B)B9B=BABCBGBIBOBUBYB[BaBeL#ceA5A7;A9W;EAC:A;@:A ;iA=@xpB$p&pB(هpp݉vȤ,lmpuȤp65}}ˇxrecompiling ... done 9copyForValidationterrible problem in recompiling subclasses! #!AAACAp| 9class:category:q?AE AGAYAgAm? =EAIAQAEMAKAAAM #BAOp|x 9setClass:category:ASAUAWAAMA]A[AO9scanFrom:A_Ae#"A/*ceAaAciuC&'x v< #B`axwAiAkclasscategoryAoAqAsAu_sA[AO #BAp`x`#dAvȤkp`}ˇxɛ #BAps`xƚ#A#=>;?4AWppvȤ lp}ˇ%ևxt #!GpЇxd#!GpЇx#!W*4A>Ї!ćp%ЇpЇx? reorganize#"@;>AЉvȤip}ˇx #cA=>p`xOK#*:// ;OU;5 A?IsƘxipщvȤI}jpkpn։vȤDlpEpׁEvvȤou s}vىvȤo}}ˇx: #BAps`x#!A%A=]/gFBppЇx¯ 9classify:under:#OQg;{sAB#hpԉvȤ j}ˇ|=#A>AA#;?4AWplsƛp#|pp'؇x 9categoryOfElement: no such message #C !!AWAj҇pruԇՇxQ## A>AA!pwӉvȤjv}ipqwx9moveChangedCommentToFile:numbered:9fileIndex+#e;A>AA M'A/ksƨ-sƞDDpض pp&'px  will be redefined if you proceed.9#@;>=eWcAA#;?4ApсDЉvȤ>nvȤo}mu&Eևp*pvȤ op}ˇ.s}ˇx> #BW*4AAЇЇ!ćp%&&xv  methodsFor: ' #Ap!xJCategory name must be a String#OQg-{sAB#hpԉvȤi}ˇ| #OQg:{sAB#hpiv‰vȤ j}| #Asƚ@e|q? #!{pxި#OQg;{)sAB#hpvȤ iG}ˇ| #!A:p|{ #B@ps`|#d ;MAA MA>p!uȤ{kpwp|Զ9putSource:class:category:inFile:##")>W4A>"'@sƨ@whч҇Ӈp'pӇۇx organization changeFromString: #AAAA ;ip֬ p՞pԙ#|"|!| |A subclass:  variableSubclass:  variableWordSubclass:  variableByteSubclass: "#W4:A5ЇC҉uȤlppЇp}xJ9setSourcePosition:inFile:)#!5:2=)[='5+2BщuȤ$pplmHpHpp}|ȹ# A>A%gphu"|D|ё9classComment #!>pru`x*#"OQg{AWA>s=)[upABip&ׇpNpx comment: 9classComment:#" =>7ApvȤip}ˇpԇxP 9removeEmptyCategories #;s@sepxR#C @=>@WppvȤjp}ˇԇx##!!AB!A Ap$%qiAjׇpruهx-.st #"!!>BB>=uAp%&i(Jp܇x0-.pp#z̠ #!{px #A=]Ap|H!#!'7B>=)[5B@{p!pFpFp*x 9removeElement:  removeSelector: ##d4=> >W@;A ppbԇpՉvȤ kp}ˇx/#"{=WB,OB@;>=uvpᇈӇӇp&'pv)ӇpډvȤip}ˇx comment: ''#!A!!BB!pBp%&qx3-.st #"!!>B%B'>@Ap%&i(Jp܇xO-.ppo#6OQgX{B+;=WB-UA)B/A'B1A+B3B5A; B7 MA=]sAB#hp82pهڇ3pهڇ+pهڇ.pBsƙ&ppهڇ+pهڇ.pهڇ0pهڇ6YpՃ8|nilinstanceVariableNames: classVariableNames: poolDictionaries: Class named: superclasses: category: #B;sƙ ||#!W{B?>Ї"p&ЇpЇvxH reorganize #=)[>Bpp|5#F@;>=eWcBE@@pсBЉvȤ:lvȤm}ku"Eևp*pvȤmp}ˇ֐s}ˇx >#GpЇxS#//BK*I>k;w;y;;:{CBMkq;1@po"тIDLJǂKp`ppƝpsdpHvȤM p,|}ˇusdJopJ|:w:::g:k:c is reserved (maybe in a superclass)#BW{BQBSЇЇ"p&''vx  methodsFor: '#CA>BW@@Wpjsƛp#|ppևx no such message.#FW:@ {ЇЇC҉uȤ(pkṕDmpvvv}xPL#EuB]{ B_vj!kuIuAwvvwj(luvB B!ks&wGDuvvx: # A>Bcphup$||yS comment: 'This class has not yet been commented. A proper comment should include the purpose of the class and the type and purpose of each instance variable. ' #BA!prux}=GBkBm instanceVariablesorganizationBqBsB{B} X qBuBw>Bys_@ 9instance variables 9method dictionary9compiling .48DJLj~A;s@A@,O,Q@AAAAAAA>A'=A)A+AA :A @i74=@=>=A-A/@;MA%=yA =A!@AA)Q>>;=AAA#;?={=u@=@@@@== class9addCategory: organization classify:  under: # 7:=9Bp՛p$r ppsyz_Are you certain that you want to remove this method?#{ l#)#5T#2;=:BB?w::@B4@;B=#>@?,OB,O:@7%ƬsƜD|p|)ƬsƜp|pp|+ƚ*|-ƛ|/ƚ.|1ƞp҃|5Ƭp҃h|4|7Ɲp҃|X|c9template:q?uG category to add protocol to addThis class has no comment #=y:pxM #={:pxM #;;Apx{R/#"=OBB@[>:=5BB==!pШxp"#hԘxippp,.p߇p0xKEnter new protocol name protocol name organization addCategory:  before: .# =OB=5:BB==!@a>pШxp"hӘxippp)+p܇pxwPEnter new protocol name organization renameCategory:  to: 3# =>:B7@i=5B==!pШxphרp%xvȤip}ˇppp,pއpsx;N%Are you certain that you want to remove all methods in this protocol? organization removeCategory: };B B=C#EE+?E= =;BCB M BBBBe5K 9openFullViewOn:label:9context: 9interruptProcess: BBBBBP#CB5;XBBBB B55=/=1BBBBB BЇB#$ajGqr()*+(uuv-veO012su-v3veUu78-tU878-t| 9openInspectors9context9contextList9contextMenu>L? 9receiverInspector?L? 9contextInspector 9openNoTerminate#"B piBr`|9process:context:interrupted: #"B piq`|3#Bqx qB9HighlightPC#BsxqBB9ContextMenu BiBBCC C#full stack proceed restart senders implementors messages step send 9BBC!Y(~V CC cC C    @ Ā @"% A B" B"$y 81@b8p"D0 D |"@=2CC%C5-igsƬ ssp"xjcՁՁesƙq ؂ pهp" p,x9inspect:9sourceCode# CCD3BAsBs p$xq?C CCD)DD?D =ECCC MCC5K CC#!Cp|% #CCs x& q5SC CiCCCCCagain undo copy cut paste do it print it accept cancel 9CCC!YV  CC cCTCa G DGDHDHI@@ ᣀd@$@$@$@yň@&D@$D$B$Cǁ < <p@GHHN xhx  X'dĈ"D"D"D"x`!@@@88pǀD"<@"D@"DD":8p8xp"D @@ D@'80YǜYLJb""b$H B""B$HC>CHB BHAAG8 @ @ @z8"d"D$@"D"$@"|"$@"@"<qq$ $ $$By$pACDDD 9browseReferences9addField9removeField # CDACDxnq?DiDDD 5KMDC=/CCDDC5=DDDDDDDDDD#yhi#CC3sƘzpuȤz`jp#yf# A(uhvȤiC}uȤ||f# DD DDDDssƝA#$|IsƬ A&'(eI|gadd fieldDinspect\references\add field\removeCDDD##DG:h%p"GxTkCan't browse calls on this association$#=ODDD44k3CA"#hԘxqbFspri{Isap+xjq?=Enter expression to evaluate as key:#|Hi#Brbxn#D%3Cp"xsap&x0m Confirm removal of DokDDDDRDaDD 9menu commands 9compiler interface  =/C!CCCDDD5={DsDDobjectfieldDDDD2 DaDD 9doIt-accept-explain "$CCCCCCCCC=1=/=CC{CCq?D+##w;:sƚ@| p|#E5E #| |=9stack9stackOfSize:# E E E BCBsƝA#$|IsƬ A&'(eI| full stack\proceedC3#full stack\proceed\restart\senders\implementors\messages\step\send#! C;p pҚpчx# EC; Їsgss Bчpx 9resetSpaceLimits###c55s q A` xD EEE!E#E%E'E)context receiverInspector contextInspectorshortStacksourceMapsourceCode processHandleE-E/E9E; z,  5E1E3DE5BE799pc selection9inspectors 9stack manipulation 9dependents access  (4<>@B#BC3:C5C3CC-=C%C1BBBC+=/=C/C)5C'C*ABBBB9{BB EAECEEEGEIEKEMorganizationcategoryclassNamemetaprotocolselectortextModeEQESEgEiJ EUEWEYE[E]E_EaEcEeD> 9category list 9category functions9class list 9class functions 9class-inst switch 9protocol list 9protocol functions 9selector list 9selector functions*NR\hrOO= 4==K=?=U<7:=)sƝsep!|Ci&b&j(&jpdpx. EEmethodListmethodNameEEEEZ EED9method list 9method functions  OEEEE<=/q?QE u;EEEE?QEME!GE 9key:EEEEEEE#!!|b #c #|b #!`xc #!xGd #!Gв|Sb #!GEpѶж|zyb }qEkeyEEEE q   !GE{9addMethodView:on:readOnly:?>9addTextView:on:initialSelection:?@?#"$5E E EEEEEEEEEEp!"#`Auu&'qd&u&'rhu'&*ri&'&*rku-./slx Class Browser9addClassView:on:readOnly:?=9addMetaView:on:readOnly:9addProtocolView:on:readOnly:>9addSelectorView:on:readOnly:>?? #B;ps`x 6#D(5E:E F55=/=1sFp"%&`juuv)qgK,-.sku)v1vpx Method Browser on >?YH#"(5F F F F EFEFEFEFEFp!"#`Auu&'qdu'&)rhu+&'rj&u&-rl/u--rnu-1/spx~ Category Browser9addCategoryView:on:readOnly:>=u>\)>{>??)#"5F:E FEFp"%&`Auuv)qgu)v+sj܇xY Method Browser on >?YU#D45F# F F%F'EF)EF+EF-EF/55=/=1sF1p!"#`Buu&'rd&u&)rh&)&+rj-u&'rl/u&'rnQ234sk5u'v7vvx[ System Browser>>>{=u??@?Q#&*ODF5F75F9 F F;EEEF=EF?EFAAj"kvl#mp%&'dAuu*rh*u*rk**rl.u*rm0u*rou2sqx>33=L System Browser>??@?4#"$5FE: E FGEFIEFKFMFOp"%&`Auuv)qgu)v+rju-./slx Protocol Browser on =>>??FSFUFW ;;;;;;$k;;MF[!EF EEEEEF]F_FaGGGG#c4==A=GpBr#$%&#v`xw#c4==K=?pBr#$%&#v`xsv)#d +FcFeFg=Q;G=7 7G =Ѱ"kpE&()rvcpE&,)qvcxx?9on:aspect:label:change:value:q?Fi FkFyG(G? =FmGGFi =FoFsFyMFqFuFw FmF{(GgGiGw?GDM6FFFFFFFFF2%')=)3E7;/YeCmF}F 9indicatorOnDuring:9centerLabel 9displayNormal 9displayComplemented 9indicatorReverse9displaySpecialComplemented 9displaySpecial 9highlightForm:9containsKey: 9interrogateModelBFFFFFFFFFFFFG;G?GCGEGGGIGKGOGQGSGWGYGaGcGe #IrpЇxQ #IqpЇx# C i _ApDApwDx# C 3Appԃx1#F)C 3+ _ pЇsƨBppHHكx#!xļ#!|Ƚ#1̀u||#Ѐ #!FЇpчx#πQ#F@|{q?F FF FG'G/?G9 =FFFMFFF$MFF/2!#e%=)Cm-FF9cursor:9addArgument:9sendMessage"FFFFFFFFFFFFF#1ux #  pџsƨЇp|#!dxDZ#x # p|i#P#eF Fp!cBudxF9switchqF#FЇx#!cxղ#g #FFЇpҚpчx#!exU#!Gdxð}FG FFF F? =FFFFMFFFFMFFF#F}1u uȤ} uȤ}x FFGG!7F GFG G? =FG G GMG GGGMGG#=GћЇzp|` qGGG!G#G%h9{G)G+G-selectorargumentscursorG1G3G5G7'\f !79{eFCm/F2=)%-F#!{# 3 'G=sƛp|"|ӾqFy #!)FGAp pчxqFy#!x$#I _+C+ { $pЇBphEpvupBB؃EpBBڃix#!x4# aFFYIpЇpчp҂sƬ pԇpՐspӇxZ#! 7FFF;GMsƬ pӚpґpёpЇp$xq?Fy'#C _+C 5+ { )pBpjEpvupBBكEpBBۃjx#!x6 #GUpчxqFy#?C 3pЇsƨ BppՃx# e _G[G]G_pBт rs#$x9isOnqFy#Ӏֻ#!FIpЇpчɇpчpЇxu#9 3 sƨ px}FiGkGmGoGqGsGucomplementedlabelselectorkeyCharacter highlightFormargumentsGyG{GG'l  G}GG 2G 9controller access 9window access9label access 9deEmphasizing   "(,26eCm/FEF%')7FFFFY;FF}FF2=)3{MGFeG #c=)/[ a GpmDFՈ|"qFkGGGFeMG;FGG #!;GƜp x!qFi #/Ѷ|k!GGGG<F;instanceclass#c=#===M=+pBr#$%&#v`x6{#c2=)=%=;pBr#$%&#v`xE|#cEEEEpBr#$%&#v`x'z#c 55=/=1pB#$%v`xT}GGGGG 9subview creation F EEEEEE from #:{" #sƚA||d#!'|y##G//GGpuȤB|iԉvȤjq}|? 9indexOf:ifAbsent:9writesField:9readsField:2#F5k5::;-G25+2jwvȤm}kppsuȤs}lsƛp|ƨp(px selector changed!3#DG* 2G;S G֬ ppdӁB8jsƬ ppdӁB#ѬkћvrvkvBs|v9getSource 9decompile:in:method:#::@"hpp҉vȤi}ˇ|*` #!:p|u#G |<message selector and argument names "comment stating purpose of message" | temporary variable names | statementsN#*OQg ;{I:;G //*W;;suiAB#hpՉvȤFkviهjv%-wvȤlه燈ه}ˇ0Đs}ppr|yF [also a #4@|#";:pЉvȤip}ˇx! #!;;:Ap`x/##::;; eWcGG;%pipӨxpщvȤj}|pDՇ()pxpщvȤj}|slconflicting methods for  in #z~d#!;GHH pApBpCx*qGH9SelectorsOfConflictMethods>!HqHH 9SelectorsOfCopiedMethods>!H qHH9SelectorsOfDirectedMethods>!H#d GuȤA}kxH#;sƚB|h|^%#h HkIHH@kmounvFDsƨqr⇣|9methodArray9scanFor: 9refersToLiteral:#";H#H%pщvȤ iӜr}|9selectorPart9isCompound#! H)H+'H5;Ap|sƚA||Zo 9whichClass:selector:q?H- H/HOH{H? =EH1HGH- MH7H3H5H) 9makeConflictingMethods9makeMethodNotImplemented H9H?HC #H;H=p!|.) 9setStatus: 9conflictingMethods #H;HAp!|p) 9methodNotImplemented #BHEp|) 9setWhichClass:setSelector:HIHKHMH3H5H)$MHYHECHQHSHU2HW!5H; 9isMethodNotImplemented9isBad9whichClass 9isConflictingMethods"H[H]H_HaHcHeHgHiHkHmHoHwHy#Babx@( #:|# #а|$ #HA |&& #HAH=!ƙq |% ## ## #H= |% #! HWHQHU2pК|pњ||$$ #!!|% "#!{HqHAHsH=Hu"Ɯ!x$Ɯ#x%'ć(ćx& MethodDescription(methodNotImplemented)MethodDescription(conflictingMethods) MethodDescription(#5|e# #!`x&( H}HHstatuswhichClassselectorHHHHB qs52CHU!HSHWHQH;HE#c #$ H5H+;;H3HQAjp҉vȤki՚s՜B sA|}ˇ||z#;GHH pApBpCx#(#$'H GH)H+A;iCuȤD}pjEuȤD}pkGp|p|pH#%*HH%HH#;'; H HH>H;g;;:HS;!HCѨ |ik(Ƭ pppFe'|/ƞpDIjpښjp+|D |p3221ppFe'|T9NotFound9classPart9OK9all 9HierarchyViolation.## 5:2;]2HppsuȤ{jip%|E#% H eWcHH;%;gH ;;m;AuȤB}vȤkps Cԇ'(s}ˇLuȤB}vȤkpvȤl}ˇpLos}ˇxaiconflicting methods for  in b#(0'H GA;;mHQ;HW;;HUH5;!C;]2; ;lCuȤD}pmEuȤD}pnypiڜpyܜpz pppEmp77pjqkvȤ oC}ˇ pTp2ppCvyB 9fieldsTouchedv#'0;: 3HOQg{H0WH;!spщvȤm}iClv‰vȤ n'}JK,j.u!kv‰vȤn퇈퇃}vȤGm3퇈5ću!kv‰vȤn퇈퇃}5}ˇp6xargall.self #Bz!#;/;%eWcHqhpЉvȤ ip@}ˇ Cԇp(x& has conflicting inherited methods -- consult browser for their names#!:pp|j#;;@hpщvȤi}ˇ|wh# @ u!u"ubx#;3|| # :pЇxZ#;7|~#'1;_ [gW;_pщvȤ hEHJp}|#!H/:Cp!xJLsuperclass must be a class-describing object#HHHH ;ip֬ p՞pԙ#|"|!| | subclass:  variableSubclass:  variableWordSubclass:  variableByteSubclass: #W4 M;A5ЇЇlppx#!axQ #!H;Spp|Q 9decompile:in:#u| #c;MpuȤ{| #;}@hp|{a #Ap|C# 5:25+2pplmp|G#;[k@hpvȤ iƙs}|0} #A;ip| D#"H@|q?H HIKSKK?K =HK5KKH =EHI IMHeOHI# ] aIBqrsaBtuvwx_ qII 9SpecialConstants  #!I 2Sp|` 9method:pc:I IIeO HIIK!K'?K3$MI)I CKIIIIII!I#I%I'H-5 9addFieldIndexTo:9nextByte9interpretNextInstructionFor:9willStorePop9willSend 9followingByte 9interpretJump9interpretExtension:in:for: 9addSelectorTo:"I+I-I/I1I3IWIYI[I]I_IsIuI{I}#B`ax^ #+5p"#|FD .##5k +pi"v|#(r&#%#v|'(pvj&&v|xO #5p|T #%J5 I5I7I9I;"I= I?IA ICIIEIGIIIKIMI%IOIQIS1_IUpli!j!kvau|v|wv|'&|)v|*&|.,|,|9@u|,P|,|3 P,2|3|6|6p87|,pz|=,v;|,vr\|?&iva, )>;|'>3\|v!rv# |3&!r&# |3vr6 |xWG 9pushReceiverVariable: 9pushTemporaryVariable: 9pushConstant:9literalAt: 9pushLiteralVariable:9popIntoTemporaryVariable:9popIntoReceiverVariable:9pushReceiver 9methodReturnReceiver 9methodReturnConstant: 9methodReturnTop 9blockReturnTop unusedBytecode9jump:9jump:if: 9send:super:numArgs: 9specialNargsAt:# 5+ph$q"#|E #5`+ ph!z#"|%&|D #5pv|S ##5+ .H@Nph#$va!|'(wa%&pv|{F #g4I5I7I9I;I=IaIcIeIgIAI?Ii@(;ISIkImIoIq& m nvau(u|v|wv|&v|v$u|v|wp*&v|w$u|v|wp*&v|35/k/lvkvlwv2q|3|6|8|p9xgW 9storeIntoReceiverVariable:9storeIntoTemporaryVariable:illegalStore9storeIntoLiteralVariable:9popIntoLiteralVariable:9doPop9doDup 9pushActiveContext unusedBytecode;##5@(;kI;+ 1_`pi!x+- p,v J+v$'(Ӭ pv"pwjpvsx}Q &#% 5Iw Iypij+Cʘy"l% $"v #wvaz2U 9endPC #T #.T }IHJ  IIIII? =HIIIMIIII$M.IIAICIEIGIIIIKIOIQIISIaIcIgIiIkImIoI5I7I9I=I? 9printInstructionsOn:"IIIIIIIIIIIIIIIIIIIIIII #!IIp"x5 popIntoRcvr: #IIp!x8 self #IIp!xE4 returnSelf #!IIp"x3 return: 8##I:I5  3':{Wч"ćvvȤjp&i)('ćć}t,ćчއcx> 9storeStringRadix: #IIp!x4 returnTop #IIp!x1 blockReturn#!IIp"x2 jumpTo: #B IIIp#"x3 jumpFalse: jumpTrue: #"Iw5IIbpicpp"x0 q?I#cIIIp#"x: send: superSend: #!IIp"x<= storeIntoRcvr: #!IIp"x= storeIntoTemp: #!IIGp"x< storeIntoLit: #!IIGp"x4 popIntoLit: #IIp!xm2 pop #IIp!x%2 dup #IIp!x7 pushThisContext: #!IIp"x)9 pushRcvr: #!IIp"x: pushTemp: #!IIp"x7 pushConstant: #!IIGp"x8 pushLit: #!IIp"xQ6 popIntoTemp: IIstreamoldPCIJJJ\\ Jq 9instruction decoding,.IIKImIkIOIQIGIEIIIiIAI?IoI9I=ICI5I7ISIgIaIcI J IJGK K K?}K =HJ J?J M JJJJJJ9trace: 9initPrimitives 9tallyMethods: 9tallyInstructions: 9runSimulated: JJ3J7J9J;#J5@J2_J!!vȤiCh'p%}x #doPrimitive assumes 3qJ#J% 9TryPrimitiveMethodsJ'J+J-J/J1 #J)@ |{ 9primitiveFail #J) @ | #J)z@ | #J)@ | #J)@ | #$ WJ5 ku@kivȤjƚssƨA}|9runSimulated:contextAtEachStep:## WJ5 kIs@jvȤi}| #"J5 vȤi}|8## J5 e*IW{ gJ= 5'2{ivȤ:jƚs1sƬ BӇ$ćBׇJ,臈凈Ӈ߇A}|9depthBelow:JAJCJE JJJJJM|JcEE2 5' )J5I5I7I9J=I=*AI?IAICIEIGIIIOIQIS-=JIJKJMJOJQIaIcJSIgIiIkImIoJUJWJYJ[J]C?CIyJ_CJaACI-.00-5 9primDecrementStackp9tryPrimitiveFor:receiver:args:9swapSender:9activateMethod:withArgs:receiver:class: 9send:to:with:super:9return:to: 9singleRelease9shortStack9pop9hasSender:9doPrimitive:receiver:args:9stackp: 9primIncrementStackpJeJgJiJkJoJqJsJuJwJyJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJJKKK #ENp!|#p|## mC @!jpAԁAsr⇣|~#!JmsƘ{p |{q?}J #BJmsƙ|p@||K#;k5'5pp҉vȤh}|t##GpЇx## JUpisƙqƨ jчixq#CJ{J}JJ *AJYқp!pӇjEppƨ ʇjp|simulation of blocks with ^ can run loose 9hasMethodReturn 9pushArgs:from: #!-=?5'ppvx7 #!-=yppvx)#!-=pxP## piujƙqsƨ ivj|) #!-=px#Ipp| #!yJYpvpx #!A5'JYpvpx* #-=5'ppx #JS5' yppp| #!JS ypp|, #JSJY yppp|#!ax #BIOJJYppx@9eqv:&#eJYJ-=JQ@luȤp}pk(ƙq'Ƭ p%psxp|Cant simulate halt. Proceed to bypass it. #!J_ppvx #Jmv|.#eJ)JJ -=?J +5J]vu |ҁC# |#p|' pv|*؁Du |pi|x 9objectAt:9flags 9numTempsField#"i`| #JCWAp|9sender:receiver:method:arguments:2#:{I;52_5JKJ)JO:JJ ppБlsƨ$mpen&ƨ|p|lp+,x Simulated message  not understood #!A5'pvpxy #!ypvpxA #B )-=p|. #!pʇx #!JYpʇxv#JYpЇxg #-=ppx #-=ppx#sƨvvȤhps}s`xl#OQg E IWsAB#hp%vȤi}ˇ|g#J_phpspv|#" pƘzisƨ Ƙyiz#f<-=JJy//JmJJQ J)J!2YI;;eBJ'FrpBwԃa|*Brp|- pwr|k/.|Pvlww23QUumvv7mw vwXm: vw:ym/vw:/m/p=<.ƙ|p|f 9home:startpc:nargs:q?{too many arguments to this primitive#;k5'5pp҉vȤh}|#*AqICKpppЇx[#GpЇx#"JaJIsƙubuipӇspipчs|N##J*AJ[CIpЇiƙqpjipӇxj #Jmv|#BJ_AJm!p|pB|z#5;k5':pjpvȤh}i|#!IJmsƘ{p |{#J5+1C?C2KpщvȤh|ppshp|' 9setTempNamesIfCached:# JJyJmAppw`|g#!GpЇx#BGpЇx#1#$;k5'5JIJJ{QKpǁCp҉vȤi}j&Ƭ #ćpxƨ )ć*ć+x})~9who9?>>#GpЇxe# )psx#BJmsƙ|p@|| }K stackpKKKK  +CJK!;qKsK 9debugger access 9system simulation9implementation dependent accessing 6P^`hl|@y55'C00-ImIkIOIQIGIEIIIiIAI?IoI9I=ICI5I7ISIgIaIcJ=J[C?- )2 JWJUEEJMJO.#JY-=JSJQCJ5*ACIJ]JKIAJIJaJ_{J!K#K%senderpcK)K+K/K1K-s9decoding CKIII#III'I!5I-HI%I {IMK7eK9 #K;K=KCKE "xcascadeqK?KA9CascadeFlagcascadeargumentqKGKI9ArgumentFlagargumentKMKOKQeM>Kc I5I7I9I=I?IAICIEIGIIIKIOIQISKUKWKYK[K]K_IaIcKaIgIiIkImIoGH9blockTo:9initSymbols:9quickMethod9decompile:in:method:using:9doStore: 9checkForBlock: 9statementsTo:KeKkKmKoKqKsKuKwKyK{K}KKKKKKKKKKKKKKKKKKKK## KgKi@ivtvȤj}ˇ|9to:by:9removeLast#"2mvAsƬ vAxK  #!mvx #"2mqƜwrƜ" sƛ!ix  #!m2x  #!I7K]px0  #!I5K]px  #mvx  #ICIIpЇчx #!I9IIpчx#mKiv x #n #! xj#QAI#KiKU22/I0_ mKa2/S/Q[ mn oljpҁCѬ urr lFӂIpJN  L2apPPvuȤ}Pr0/(J1e,pK M a'(JJeHxB#i KgKi2222m 23K=K_.@kvtvȤH}ˇll-ƛpr4mKƬnKƚspoFeFx] ##Ka2pi jt |j"##2Cu2 K2у`fCdiCevvȤ jv}x9numTemps#K2[ 2KK,7ج Dvq׬ Dqp!| improper short method9returnField 9isReturnField3# KWC}(I 2SKUIwKKY/2+5HbcpܝpہD AgA#͂pՅDpvlڙsp)| stack not empty##Kim2KEijCƙxp7#'2I#mKEII KiKU2ƨzipҁBѨa{jlp֬ Dpp凣Gkv‰vȤn}pmyz #!I5K]px[ #!I7K]px #$ImKi ij   pp  p|8 #!I=K]px  #!I=K]px  #mKixC#mK=3Aƨ AAx #m2x  #cK[3pÃ| #BG5p`|6KKKKKKKKKKKKKconstructormethodinstVarstempVarsconstTablestackstatementslastPcexitlastJumpPclastReturnPclimithasValueKKKK  5J4=s48>!KWKUK_KaIKImIkK]IOIQIGIEIIIiIAI?IoI9I=ICI5I7ISIgIaIcHGK[ KY {KEK=#:;apЉvȤh}ˇx#::@hpщvȤi}ˇ|#;[uhpvȤiv@}|#D;;)pЉvȤ kys}ˇCuȤs}jsƨʇyz,##:pisƨjʇsƨispƛsʇx̰ #B;epЇxP##;;AvȤj}ipb|#;pp|#";u;[pvȤi}xɲ #;@hpB| ~ # :pЇxG#";;gpЉvȤiƙqys}ˇz #1!|B#C;q;kuȤsƟpʇp|jpƛpʇ|jpʇ|r #!%;epчxbS!## GG;S ;jDӬ ppaAisƬ ppaAs|##OQg {K3KsAB#i%v׉vȤj(}| unboundMethodwith:#L;;w;@apщvȤhp}ˇpӇx@q?M#":;upЉvȤ iʇ}ˇx#!sƨuȤs}љscxdK#!L k[;psƝFp#xJ  is not my subclass#!';{xsƘ{|## ;;}pivȤj}ˇvȤ js}xb #!w;:pp|y# L[ L; sƙ |p՟Cp|C|e 9otherSuperclasses ##C; [gWLpiṕBvIK,|. ^self conflictingInheritanceErrorW#i{I:;L: '1//*:L>B;pӇpplv$'vȤmӇᇈӇ}ˇ+ćpkpPƬv-vȤn}kwȤ HoҲ}1vȤ npvr}ˇx. [also $a... all the Metaclasses ...#$: %ivȤkpju}ˇx#$//k pijvvȤ k}|#DvȤjv‰vȤkƜps}}ˇx2#"G @;L); AuȤB}ipxpp'seppAhxconflicting inherited methods#C ;;:kpЉvȤj}ˇp ppxq#|Hu#d: %kux #A p|D #;Iphp|g#@|#@|6#D';e;G H:;;#jpчCuȤF}pppCbGuȤF}pppGbp p؉vȤk}ˇxOM#!;euȤxpчx;#!:;pysƘz| #1@!|GC# |_B#!|on#!%;e;#pчpxDR!##-;-pipӉvȤj}ˇsƞF|}@LMLOLQLSsuperclassmethodDictformatsubclassesLWLYLiLk| qL[L]L_LaLcLeLgBy_s9creating class hierarchy9creating method dictionary9accessing class hierarchy9accessing method dictionary9accessing instances and variables9testing class hierarchy9testing method dictionary*2H`vzu;s: ;i ;K;Q;:;y;w;;5+;];A7;m;U;5';:;I;};; ::{;:m;;/;#;5;;;k;::;;;3;O//;7-;;Y:;:;W;g;=;;E:/#;{:;_;;G;M;a;;U;':;!;C;S8W;);-::;::;[;u;c;:;9:;?;;%;;;;+;q;e;1; ;;;;5-;o;;; {HH G3"is a global. Smalltalk is the only instance of SystemDictionary and holds all global variables." 9allBehaviorsDo:% is a Dictionary. It is a pool which is used by the following classes" is h#"0S:G[g/3Q*::L{*L}LL* LC:9IvИ{նpC|'&rpC|)(rpC|+*rpC|-&r,|-.|2wr 0C1|7wƒSip6s541|ss{b?"An instance of class Array. The Numbers, Characters, or Symbols between the parenthesis are the elements of the Array.""An instance of class Symbol." "An instance of class Character. This one is the character ."$"An argument to this block will be bound to the temporary variable #K!:E:9:7CAS=-:'L:I:C:?:K:=:A/!(u:M:G:;LBщuȤ.IpjvȤ Jڙq}uȤs}s pksƛpksƛksƛ.CMCVvȤH}U5p0lsƬp1lsƜp2lp3msƬpmsƞp4EsspEsƛ.DMDsƛ.EMEvp8Fp7Fp9osƙ.osƙ.nI}u;|| A1"Sorry, I can't explain that. Please select a single token, construct, or special character." # :`abcdxH@0#$;C:LL:'LLsƘ{kvȤjӉvȤi}uȤs}s}uȤ{kk&'H)*|Lk "is an instance variable of the receiver; defined in class " browseAllAccessesTo: ''.A#'+155:-]KLL3sƘ{simvȤn}Bu³G֐rsclՁA{vȤn}Bu ܳ+C*C|\z"is an argument to this method""is a temporary variable in this method"4##O*w+ LLLLvBѨ  vr{CiEjŨ{ ','|'(*'|q" (= ) is a  is a ;#$:SLL:5LLLLLsƘ{Aj&%B#B *-.|ivȤk}uȤs}sƘ{*+,|=m these classes many classes" is a message selector which is defined in 8. To see the definitions, go to the message list pane and use the middle button menu to select 'messages'." is the selector of this very method! It is defined in =. To see the other definitions, go to the message list pane and use the middle button menu to select 'implementors'."#&8;=/=C;LL:'LLL;'-OQ LqL)LsLsƘ{CѐlvȤm։vȤi}uȤs}s}uȤs}ksƨ(*K,-.|vȤm߉vȤ j0kqr}uȤs}s}ˇsƞQ0QksƨMST̃2lVvȤm߉vȤj}uȤs}sĐs}57V89*K,V8;.|{X"is a class variable; defined in class "Smalltalk browseAllCallsOn: ( classPool associationAt: #)."is a pool variable from the pool , which is used by the following classes $ associationAt: #LLLLLclassselectorinstancecontextmethodTextLLLL~fL9explaining:::A:G:?:C:M:K:7:=:;:I:E:9{:'1"Sorry, I can't explain that. Please select a single token, construct, or special character. Also, please cancel or accept.""#!9LL"qp |n3)5::q9=#"- 58W6%8Y3 M5=pЇ ipjpkppuȤpه*|hpܶp°vpNp0pه|*# )5= C8Yph%px6}LM L9M,M ? =9LLLMLLMMMMM # = M Ө њЇp҇zp|9isSelectedMMMM69{ M9M#,M)? =9MMMMMM!M!M!MM%5M'#=-6%|p҇pp ӁЇpևxSM+M-M/M1J55M5M7M9M; R5 )::9:5M?MAMEMG+2859MC 9control activity  595=6639 #6pЇx/# 6I3ԛpҐrёЇx '#9 66A637MOp۬pp$upٛאrppp܇p xaq?6 #"66Y;MOƬpip pчppӇp&x#ceppчx}5MYM[M]partMsgacceptMsgmenuMsgMaMcMiMk+  G}GMeMgs9emphasizing9adaptor  e6%7Y;36665MMo5Mq#Ms5 Mup|; 9initialSelection:q5MyM{M}5M M%6Ms;MMMMM #3ҚpёpЇx:#M@|c9q?9#!67Mp sƨpҀx8q5#!x8#"C17/3-;M%Ƭ ipp&x9q5}M M5M&MM? =5MMMMMM9on:aspect:change:menu:initialSelection:selection:M#M5 Mp|"  9selectionMsg:qMMMMM MMM%M  MMM#!xb#M@|q?L#|<MselectionMsgMMMM: G}5M%M M initialSelectionMMMM n G} 9 Ms6%;9openNoTerminateDisplayAt:MMM 5?5KMM5=/=1=3MMMMMMMMM#{#{ #c;`bax#B@AB`sƘzy#T# M5Y5s5QFsƬ A#$%`F|e!again\undo\copy\cut\paste\do it\print it\accept\cancel\proceed#! 5Ap pҚчxE#!x #3pњЇxMMMclassbadText processHandleNNNN'DE7s 3=1=/=5{5QN NNNsourceStreamrequestorclasscontextNNNN <f1C4=s  +A+]5555555{#N# | #_ 4App|ѵ#GpЇxԳ#"Og(4$*wsAB#iuF`uaxδ#N- |#N1 |  #N5/&C| |w some local stream#{}N;O 44N=NMOO? M N?444G= NANCNGNINK#K%*# /B NEAuȤ0$ '(rAv$҉uȤ{hFǐss}|X# class###GpЇx$#!bx&#}O NO NQN;N_ NmNN? =4NSNWNOMNUNYN[N] M Na424==) NcNeNgNiNk #_ A|k # #& #!dx; #!cx }NNo NqNON N? =NQNsNwNoMNuNyN{N}$MNNNNN4)QG4) 9sourceFileAndPosition:9isInSystem 9fileOutHeaderOn: 9accept:notifying:"NNNNNNNNNNNN2#%54:5A~UpсAИ{{jDИ{ՁCD³{&l'vl'wlu{D|{ #NpwȤihrys}zw #! *{NU MW ćᇈ"ᇈ㇈ ć%ՇՇx4  methodsFor: (#C542N==)2=ACuȤ{uȤ{j%p̈p懈臈|b .#cN44/N4*WD ƜƐrrppD ƜƐrrׇ(ćههxD q?No9#$OQgxN0k{NI3WNsNsƬO[O]O_Oa.N)OetypeOiOkOmOo @4NNN) OsO O OO? =4OuOyOqMOwO{O}O MOO)9superclassName:classType:otherParameters: OOOO#=OsƜBђp|Zq?Oq#ccdex~ #O!|~ define #")==)p֬BuȤxipն pxOOO superclassNameclassType otherParametersOOOO@NO)OOOOOclassNameOOOO D 4=4G4 O4OOO? =4OOOMOOOO M O4) OOOOO #Osƛpb|%cq?O#p| c #4Op!|b doIt 2#$O*w*)KOOOw)piјxCjk% %ևŘx-(J+k³xpxcFrom 9version on #!bs`x\cOtextOOOON 4)OOfilepositionOOOP^e)!N_"444444244))Q4MPP P P MPPPPMPP!P!P!M P'4NP%)Q 9reorganization:P)P+P/P3P5P7#c)Qpx( #P-!|&  reorganize #!*{P1W ćᇈ"ᇈ ćӇx ( reorganize#!cx&#!N4WppᇈӇӇx(#4=}>P9P;5phןp%&x?'Class  does not exist in this systemP? reorganizationPCPEPGPI L_ P%N)Q4# *C*]*?"1*[!ƚpЇ$ƚq !ƙq#Ɯhp҇|j/I#I(*EO*wN==)' A-PO=G44)vȤXHpB pDDpB9jD̈kJ GJǁFGFosƙ-o߇ʐss}ˇxt As yet unclassified;##*?4)PS*[4PU*]44}pہAڬD)ƛ(rpЇ'ƬjpЇ"Ɵpe|ss$ƛ#rpЇ"Ɯp|sspŨxPreorganizemethodsFor:# *?PYP[*[%Ƭ!hpЇ%ƛ$r #hpГс@|{a. class1#f/(u*aP_*?*]O=O"ƛAr{k$vȤmpՇ&ƛr{pՇ'ƨ{}lpՇḦj| %PaPcPePg instanceVariableNames: classVariableNames: poolDictionaries:category:'#fs+m4N==)=K4} ه kpہDŨlBmجD 凈ʇxv)#D*E4)*[*]4O)p pցBլ $ƙq#ƐrpvȤ k"ƛʐs}sƜGʇx**#D44}4*E4 *K) ؇ Ũ+ ' Çpp҅$p jpp҉vȤk }x #g@!͂ x ## *KO$# j чC h Ũ iƬ ĕu|ću|4,v#E4*?Pu==)N(/(u*aPwPy=P{P}OQP4PePPPPjpЇ)(ƛGrkpЇÄ⇈%|.'(ƛGrlpЇJ̈+ʇJ̈-|10Ƭ pЇO|43pr|6 J̈5|7 J̈%|90ƬpЇJ̈8|{#q?N removeSelector:q?Orename torename:comment:PPPPsubclass: variableSubclass: variableByteSubclass: variableWordSubclass:initialize removeFromSystem inst vars for instanceVariableNames:PPfilechunkStringPPPP(ePPPs 9change set scanning 9file scanning 9expression scanning 4o4)4444444}44 ..#$4vȤkssƨ`iB}ˇsƨs`x#" )P5$)Ep!iҙuipx  '----SNAPSHOT---- #!)=pxe# ePP)up!bBcBeudvȤhq}fCg$$ x#x#vȤ huȤs}}ˇx.# A)vȤh}cCgpԇxM #uЇxz #kux#"4ki uȤ C}xx!#B 5)³ A±Ҭu  sspӇx #!´Аr|4## *gK**)rjqBŘ{i!Ç|$C|* Ç*qB؟ׇqB F|Ç|x{#"4)k)AvȤi}pӇx@#G !!: ' ")W4PPP)j ЉvȤJm kv=sƨ C''j؇ه+,ه-lvȤ npnD}ˇsƙsߐs}ˇx "*** conflict:  ***"...;#H /")$'jчlksƬ %uDrAmu2vm&wn´örvn³ҁG㇣ɣ|p#!3pЇp"upx7#&"W*4PGP)cePPAi"k vȤ#lЇ&(䇈ЇЇɉvȤmp}}߬ L-.Ї| "*** DoIts in  ***" *** no conflicts *** "*** no conflicts ***"S#g0W4P4P)/NO*wK*)#*{wP)Ї#%ЇkIp|Kl܇N܇/0/܇mnpWЇ5464Ф ЇЇ|"File: " [SAME CODE AS ABOVE]#$5 iѬvȤk}jvȤ kʝr}xR#! ))!!PpspC%|8DoIts#u uȤs}xt-# )5)uhsfvȤ jћps}ˇҬ vȤkq}fvȤk}esƙuipx`#;;[ P/NuhGAC%|{ current definition##FW*Aj"lkvȤmӇCćĐs}ˇćЇx #cbx #! ´ Аr|#B 5) ³ A ± Ҝ  spx##)Q)5Qp"p$vȤh}`|h()#=#y #!))psp|#-#D N53uzjkјzpp%x#Bk uȤ B}x^ #!Q uȤ!}|#EO*w)AjAkpDp⶞sƘyz ##!x9#"3)@̂ @̂  vȤ isp}ˇx#")vȤ is}ˇx#!3)pѕdpЁp#x #Q'sf x #u|x5#OQgdQ{Q-svȤCish vȤ)jsƚs jsƚssƝCD%h&ć(}ˇsƚٖ}|K) #Q1ud `xVQ5Q7Q9Q;Q=Q?QAQCQEQGQIQKlistNamechanges selectionIndexlistfilterremovedfilterListfilterKeychangeDictdoItDictcheckSystemfieldListQOQQQ]Q_x  QSQUNQWQYQ[9_s9filter9showing 9checking-Change 9checking-reporting 9checking-private$(,6:DHRX^h6))Ye)U)E!)))=)5)9)))))!{!u)!w!)!))))))!)))))!});)Q)))))^#%6c )5'h) U _C)oQciQuqsQ+Ai%%pjuu%(Kwwwup/lp2lSkŨ4uu%6&KwwwwwxzQeQmQg)Qi)Qkshow file4Qo)Qq)Qs show category4QwQ}QQQQ4)Qy)Q{<4N)Q)Q<)Q)Q<44)Q)Q<42)Q)Q<  2Q)Q)Q<9same  q88R#QGMcsQC=)/) 2a+i - mwnvȤ^o2ȤUMLKJIHAlDwwuuu+nmuF}}ˇ| 9valueWithArguments:q?G#$k)U)upBCwx #QQQs $k!o)oMQQc%QQQQ 9selectionIndex: 9selectionInterval 9selectionBoxOffset: 9reverseRemoved 9selectionBox:QQQQQQQQQQ#! Q/ pp氻pػJvvvu|#! cQ)Qp pӂxC9list:q)i#)I@| #QQppчx9q)i#!Qбҽpӱw| 9minimumSelection#kQ )9ppvpp|{ #QЇpxq)i #!QvpаvѸ|%#QQ / qC 57)=pЉvȤ jphCuvwiGps}ˇx #QQpЇpxiq)iQQQQ 9G}  c%QQQQQ# -!!{%pЇC҉uȤ}pՇx #-!}%pЇчp҇x  #)Їч҇xQQQQ 5ks$&.e!!!!!y!s!!}!m!{!q!o!u!!w!!!!{!G!QQRR9{9# RRR!? =R R RMR RRR MR RRR0#;C =rhiլjs kqhsƘx xukר|xI #RИzp|q?R!#6-! %=#RisƟևphu p҇pՐsx3R#R%R'R)#59{R-R/R1R3R 9{!9k5s !R7R9R;scrollBarmarkersavedAreaR?RARERG#R  !79{RCk {!9s 9scroll bar region  $.4e%-#! { RMVk*YY)?cY5 =ROVcRK$MRgRQRSRURWRYR[R]R_RaRcRee9flashCursor:9newForm9openOnForm: 9openOnForm:at: 9createOnForm: 9openFullScreenForm 9setKeyboardMap 9formFromDisplay 9newFormAtOrigin 9createFullScreenForm9fullScreen"RiRoRsRuRyUUV-V/V3V5V7#!RkxDq qRm9FlashCursor #Rq _XB##Їxuy 9edit #"RYpiчxVv #C RYRwipjwxv 9openDisplayAt:C#&.cR{sS SU _S)' U Ui'3AipjDkGv,Ol021wm56|r q?[R} RRR"RS?[ =RRRR} =RRRMRRR"# _c;R=SU 7Ahpi$&&wAڇۇxҭ @# _c=SU 7Ahpi$$wA؇هxo RRR RR RRR?]R$MR55RR]_RY%'; 9changeValueAt:put:9defaultRule9defaultMask"RRRRRRRRRRRRR#N # #!x+ #BR3pxd 9valueAt:put:# _A| #Rsƚp||9 #Rsƚp|| # _A|$ #!x %#YC# _]Rp sƨBp huuBppppكx< qR#R@| q?cRK# Buu | #!7;RpƨpЇp!x© q?]R}R}RRrulemaskRRRRD G}9G5s  ]_%R'Y;55RR{MRRRRMR5cRR5YR 9updateDisplay9workingFormRRRRRRRR# u3 _ 3рuuCCԃpxƒ #!cRp тxK qR}# 3ppxς #Ѐ #37&ppӇxu ## C_]huuᇀCpppp׃xD #Rpчsx_ qR} #BR3px S displayedFormSSS S  95  RcRYR55 9makeFormEditorMenuq?gS STU?gU =STSMSeSR#0*SmS`'1SS7S9SeTyO _T{ST}TTT@!h"vȤmu}ˇ$vȤm%}ˇh'i(l)j@̂v!vȤ'nLkO102ʇ3J}O4O6x @@H @`HS!S#S%S'S)S+S-S/)%a 3S1S3S5Q!))))))))))):k:k:g:k:k:k:g:k:k:k:k:k:k:k:k:k:g:k:k:k:kS;S=S?SASCSESGSISKSMSOSQSSSUSWSYS[S]S_SaScselect.form singlecopy.form repeatcopy.formline.formcurve.formblock.formover.formunder.formreverse.formerase.formin.formmagnify.formwhite.form lightgray.formgray.form darkgray.formblack.formxgrid.formygrid.form togglegrids.formout.formqSgSi9FormButtons,*SkSSSSSSSSTT TTT)T3T=TGTQT[TeToSmSS:k SoS}SS?a =ESqSuSmMSsSwSyS{MSS(c#.OS 9initialState:9initialStateSSSSSSSS#[2 #3 # 3 #!bx!4 #!`x3 #!ax2 #1 #!cx2 SSSSoffsetformvalueinitialStateSSSS` OSS#(c. cS@@SB ჀჀჀჀSmSSS!:k cS@@SB SmSSS#:g cS@@SB ??????~~<SmSSS%:k cS@@SB ??xSmSSS':k@ cS@@SB ??SmSSS):k cS@@SB ????SmSSS+:g cS@@SB @TUU_UWU_UTPSmSSS-:k@ cS@@SB @TUUUUUT@SmSSS/:k cS@@SB ??SmTT:k cT@@T B `  `ႀSmT T:kH cT@@TB ??SmTT):k` cT@@TB SmT!T#%a:k` cT%@@T'B SmT+T- 3:k` cT/@@T1B "" "" "" "" "" "" "" "" "" SmT5T7S1:k` cT9@@T;B UU`UU`UU`UU`UU`UU`UU`'UU`UU`SmT?TAS3:k@` cTC@@TEB SmTITKS5:g` cTM@@TOB SmTSTUQ:k` cTW@@TYB aaaaaaaSmT]T_:k`` cTa@@TcB SmTgTi:k` cTk@@TmB !!!!!!!!!!!!!!!!!SmTqTs!:kH` cTu@@TwB q?aSm/smalltalk/system/initialization//smalltalk/system/initialization/specialborderform.formqTT 9SpecialBorderForm cT@@TB /smalltalk/system/initialization/borderform.formqTT9BorderForm cT@@TB TTTeMTTT%TTTS TT 9makeColorConnections:9subViewContainingCharacter: 9makeGridSwitch: 9makeConnections:9makeButton:9makeSwitch: 9makeViews:for:TTUUUUUUU#"GFpщvȤ i|s}{m (##SeTTTS:gTUTT@j%BӁABсAuȤ}uȤ}pxU 9newOffq?T TTUUmUu?U =ETTT MTTT9newOn TTT #TTp|Ϭ 9initializeOffqT#Tp|@ #TTp|m9initializeOnqTTTTTT$MTTTFTTG[!TTTTT9set9turnOn9onAction:9offAction:9isOff9turnOff9doAction:"TTTTTTTTTTTTUU#r`sasbx,#q`sasbxk #TTG[pҚpёpЇx#! Tp pҚpчxl #+Tpќq`pЇx#+TTpҬ q`pЇpx #Tpsasbx#ҥ #+G[pќr`pЇx#!iax#!ibx:#A|#+TG[pҬ r`pЇpx #!sƨɇxө}U1U U TUU#?U/ =TU UUMU TU #Up!{̔Buttons cannot be created in the on stateUUUTMUTTUU! #Tppxʓ#r`xTU%U'U+U-$lU)9stateTT{ U3TUAU]Ua?Uk =TU5U9U1MU7U;U=U?MUKUCUEUGUIT; 9isConnectionSet 9notifyConnection9connection:9connectionUMUOUQUSUUUYU[#sƘzy #3UIUCpҜppxp #!-cpx4##UCUWppқpxq?U1#+UETTpӬ q`pЇpчpx #!TCppЇxU_connectionUcUeUgUi$ U)UI  TUIUGUCUE;{UoUqUsononActionoffActionUwUyU}U'> E7U)U{s9action!TG[TFTTTTTTT{9changeTool:#U@| q?eU UUU?eU =UUUMUUUUMU!#U 9processMenuKeyUUUU#q m;AC| #U ҚpёpЇx # T wFChs҇x` #q p|ԇ UUUU 9{#!UC{'8#& @SeTUWTS:gTUUGTC=)TS@ivȤ7mAk&CԁBCҁBuȤ}plvuvv.}ˇvx #$SeTUTUTsU@jBiuȤ}pkGx q?Uq?F!##SeTTTS:gTUT@j%BӁABсAuȤ}px ,# TTk T"T$&(*pvpw#p$%p&p'p)*p,p-p.p/x& +#DcGME) =#SU _jBkuuvMp|͘ @#&&@SeTUWTS:gTUUGTFTC=)TTS@ivȤ;mAk&CԁBCҁBuȤ}plLvuvv0}ˇQv2x) UUUU UG}s 9subView access S T%TTTTTT {TSeT9toolMenu:Form Editor #Rcphчxcu Q#TUS!US#US%US'US)US+US-US/UUV)V%aV 3V S1VS3VS5VQVV!V%!V) "$&(*,.02468:<>߀ဢ〤倦瀨xe{ qU9SelectKeyqUS! 9SingleCopyKeyqUS# 9RepeatCopyKeyqUS%9LineKeyqUS'9CurveKeyqUS)9BlockKeyqUS+9OverKeyqUS-9UnderKeyqUS/9ReverseKeyqU9EraseKeyqV9InKeyqV)9BitEditKeyqV %a9WhiteKeyqV 39LightGrayKeyqVS19GrayKeyqVS39DarkGrayKeyqVS59BlackKeyqVQ 9TogglexGridKeyqV# 9ToggleyGridKeyqV' 9ChangeGridsKeyqV+!9OutKey #Rq _BЇx$x # V1 _XB##$$xz 9editAt:# RY _pB#$|z #R[RAxx #RkR]7-V9V;V[V]rpчC$&xq accept cancelqV=V? 9YellowButtonMenu 1VAiVCVOVU accept cancel9VEVGVI!Y^( VKVM cVQT4VSP 88pǀD"<@"D@"DD":8p8xp"D =!uu"vw$%w#G&'v(*),}| 9borderWidth:mask: i  9setColor:xn